Commit 76b51c0c authored by Alfredo Di Napoli's avatar Alfredo Di Napoli

Remove InsertDB class, add publishNode and shareNode

This commit removes the `InsertDB` typeclass, an indirection which
wasn't very useful as it was being used in exactly one place in the
whole codebase (i.e. the share code).

Talking about share, this commit refactors things ever so slightly so
that we have a dedicated `shareNode` operation rather than using the
low-level `insertNodeNode`.
parent c700b016
......@@ -18,41 +18,10 @@ https://dl.gargantext.org/2023-06-09-gargantext-db-graph.svg
-}
module Gargantext.Database ( module Gargantext.Database.Prelude
, module Gargantext.Database.Schema.NodeNode
, insertDB
-- , module Gargantext.Database.Bashql
)
where
module Gargantext.Database
( module Gargantext.Database.Prelude
, module Gargantext.Database.Query.Table.NodeNode
) where
import Gargantext.Prelude
import Gargantext.Database.Prelude (DBCmd) -- (connectGargandb)
-- import Gargantext.Database.Schema.Node
-- import Gargantext.Database.Query.Table.Node
import Gargantext.Database.Schema.NodeNode -- (NodeNode(..))
import Gargantext.Database.Prelude
import Gargantext.Database.Query.Table.NodeNode
class InsertDB a where
insertDB :: a -> DBCmd err Int
{-
class DeleteDB a where
deleteDB :: a -> DBCmd err Int
-}
instance InsertDB [NodeNode] where
insertDB = insertNodeNode
{-
instance InsertDB [Node a] where
insertDB = insertNodes'
instance InsertDB [NodeNodeNgram] where
insertDB = ...
-}
......@@ -27,10 +27,8 @@ import Gargantext.Database.Admin.Types.Hyperdata.Any (HyperdataAny(..))
import Gargantext.Database.Admin.Types.Node
import Gargantext.Database.Query.Table.Node (getNode, getNodesWith)
import Gargantext.Database.Query.Table.Node.Error (HasNodeError, errorWith)
import Gargantext.Database.Query.Table.NodeNode (deleteNodeNode, queryNodeNodeTable)
import Gargantext.Database.Query.Table.User
import Gargantext.Database.Query.Tree.Root (getRootId)
import Gargantext.Database.Prelude (Cmd, runOpaQuery)
import Gargantext.Database.Schema.Node
import Gargantext.Prelude
import Gargantext.Utils.Tuple (uncurryMaybe)
......@@ -42,12 +40,9 @@ publicNodeTypes :: [NodeType]
publicNodeTypes = [NodeDashboard, NodeGraph, NodePhylo, NodeFile]
------------------------------------------------------------------------
data ShareNodeWith = ShareNodeWith_User { snwu_nodetype :: NodeType
, snwu_user :: User
}
| ShareNodeWith_Node { snwn_nodetype :: NodeType
, snwn_node_id :: NodeId
}
data ShareNodeWith = ShareNodeWith_User !NodeType !User
| ShareNodeWith_Node !NodeType !NodeId
------------------------------------------------------------------------
deleteMemberShip :: HasNodeError err => [(SharedFolderId, TeamNodeId)] -> Cmd err [Int]
deleteMemberShip xs = mapM (\(s,t) -> deleteNodeNode s t) xs
......@@ -94,6 +89,8 @@ nodeNode_node_User = proc () -> do
shareNodeWith :: HasNodeError err
=> ShareNodeWith
-> NodeId
-- ^ The target node we would like to share, it has
-- to be a 'NodeFolderShared'.
-> Cmd err Int
shareNodeWith (ShareNodeWith_User NodeFolderShared u) n = do
nodeToCheck <- getNode n
......@@ -105,14 +102,10 @@ shareNodeWith (ShareNodeWith_User NodeFolderShared u) n = do
then errorWith "[G.D.A.S.shareNodeWith] Can share to others only"
else do
folderSharedId <- getFolderId u NodeFolderShared
ret <- insertDB ([NodeNode { _nn_node1_id = folderSharedId
, _nn_node2_id = n
, _nn_score = Nothing
, _nn_category = Nothing }]:: [NodeNode])
ret <- shareNode (SourceId folderSharedId) (TargetId n)
void $ CE.ce_notify $ CE.UpdateTreeFirstLevel folderSharedId
void $ CE.ce_notify $ CE.UpdateTreeFirstLevel n
return ret
pure ret
shareNodeWith (ShareNodeWith_Node NodeFolderPublic nId) n = do
nodeToCheck <- getNode n
......@@ -123,14 +116,10 @@ shareNodeWith (ShareNodeWith_Node NodeFolderPublic nId) n = do
folderToCheck <- getNode nId
if hasNodeType folderToCheck NodeFolderPublic
then do
ret <- insertDB ([NodeNode { _nn_node1_id = nId
, _nn_node2_id = n
, _nn_score = Nothing
, _nn_category = Nothing }] :: [NodeNode])
ret <- shareNode (SourceId nId) (TargetId n)
void $ CE.ce_notify $ CE.UpdateTreeFirstLevel nId
void $ CE.ce_notify $ CE.UpdateTreeFirstLevel n
return ret
pure ret
else errorWith "[G.D.A.S.shareNodeWith] Can share NodeWith NodeFolderPublic only"
shareNodeWith _ _ = errorWith "[G.D.A.S.shareNodeWith] Not implemented for this NodeType"
......
......@@ -147,6 +147,21 @@ getNodesWithParentId n = runOpaQuery $ selectNodesWithParentID n'
Just n'' -> n''
Nothing -> 0
-- | Given a node id, find it's parent node id (if exists)
getParentId :: NodeId -> DBCmd err (Maybe NodeId)
getParentId nId = do
result <- runPGSQuery query (PGS.Only nId)
case result of
[PGS.Only parentId] -> pure $ Just $ UnsafeMkNodeId parentId
_ -> pure Nothing
where
query :: PGS.Query
query = [sql|
SELECT parent_id
FROM nodes
WHERE id = ?;
|]
-- | Given a node id, find it's closest parent of given type
-- NOTE: This isn't too optimal: can make successive queries depending on how
-- deeply nested the child is.
......
......@@ -19,19 +19,29 @@ commentary with @some markup@.
module Gargantext.Database.Query.Table.NodeNode
( module Gargantext.Database.Schema.NodeNode
, deleteNodeNode
-- * Types
, SourceId(..)
, TargetId(..)
-- * Queries
, getNodeNode
, isNodeReadOnly
, selectDocNodes
, selectDocs
, selectDocsDates
, selectPublicNodes
-- * Destructive operations
, deleteNodeNode
, insertNodeNode
, nodeNodesCategory
, nodeNodesScore
, publishNode
, unpublishNode
, queryNodeNodeTable
, selectDocNodes
, selectDocs
, selectDocsDates
, shareNode
-- Queries on public nodes
, selectPublicNodes
, isNodeReadOnly
)
where
......@@ -295,3 +305,22 @@ node_NodeNode = proc () -> do
nn <- optionalRestrict queryNodeNodeTable -<
(\nn' -> (nn' ^. nn_node1_id) .== (n ^. node_id))
returnA -< (n, view nn_node2_id <$> nn)
newtype SourceId = SourceId NodeId
newtype TargetId = TargetId NodeId
shareNode :: SourceId -> TargetId -> DBCmd err Int
shareNode (SourceId sourceId) (TargetId targetId) =
insertNodeNode [ NodeNode sourceId targetId Nothing Nothing ]
-- | Publishes a node, i.e. it creates a relationship between
-- the input node and the target public folder. It fails if
-- the 'TargetId' doesn't refer to a 'NodeFolderPublic'. Use
-- 'getUserRootPublicNode' to acquire the 'TargetId'.
publishNode :: SourceId -> TargetId -> DBCmd err ()
publishNode (SourceId sourceId) (TargetId targetId) =
void $ insertNodeNode [ NodeNode sourceId targetId Nothing Nothing ]
unpublishNode :: SourceId -> TargetId -> DBCmd err ()
unpublishNode (SourceId sourceId) (TargetId targetId) =
void $ deleteNodeNode sourceId targetId
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