Commit a2db09ac authored by Alexandre Delanoë's avatar Alexandre Delanoë

[API] Node User

parent b2128170
Pipeline #752 failed with stage
......@@ -367,15 +367,14 @@ serverPrivateGargAPI _ = throwAll' (_ServerError # err401)
-- TODO-SECURITY admin only: withAdmin
-- Question: How do we mark admins?
serverGargAdminAPI :: GargServer GargAdminAPI
serverGargAdminAPI
= roots
:<|> nodesAPI
serverGargAdminAPI :: NodeId -> GargServer GargAdminAPI
serverGargAdminAPI n = roots n
:<|> nodesAPI
serverPrivateGargAPI' :: AuthenticatedUser -> GargServer GargPrivateAPI'
serverPrivateGargAPI' (AuthenticatedUser (NodeId uid))
= serverGargAdminAPI
= serverGargAdminAPI (NodeId 0)
:<|> nodeAPI (Proxy :: Proxy HyperdataAny) uid
:<|> nodeAPI (Proxy :: Proxy HyperdataCorpus) uid
:<|> nodeNodeAPI (Proxy :: Proxy HyperdataAny) uid
......
......@@ -38,8 +38,6 @@ module Gargantext.API.Node
where
import Control.Lens ((^.))
import Control.Monad ((>>))
import Control.Monad.IO.Class (liftIO)
import Data.Aeson (FromJSON, ToJSON)
import Data.Maybe
import Data.Swagger
......@@ -59,6 +57,7 @@ import Gargantext.Database.Config (nodeTypeId)
import Gargantext.Database.Flow.Pairing (pairing)
import Gargantext.Database.Facet (FacetDoc, OrderBy(..))
import Gargantext.Database.Node.Children (getChildren)
import Gargantext.Database.Node.User (NodeUser)
import Gargantext.Database.Schema.Node (getNodesWithParentId, getNodeWith, getNode, deleteNode, deleteNodes, mkNodeWithParent, JSONB, HasNodeError(..), getNodeUser)
import Gargantext.Database.Schema.NodeNode -- (nodeNodesCategory, insertNodeNode, NodeNode(..))
import Gargantext.Database.Node.UpdateOpaleye (updateHyperdata)
......@@ -94,13 +93,13 @@ nodesAPI ids = deleteNodes ids
-- TODO-EVENTS:
-- PutNode ?
-- TODO needs design discussion.
type Roots = Get '[JSON] [Node HyperdataAny]
type Roots = Get '[JSON] [NodeUser]
:<|> Put '[JSON] Int -- TODO
-- | TODO: access by admin only
roots :: GargServer Roots
roots = (liftIO (putStrLn ( "/user" :: Text)) >> getNodesWithParentId 0 Nothing)
:<|> pure (panic "not implemented yet") -- TODO use patch map to update what we need
roots :: NodeId -> GargServer Roots
roots n = getNodesWithParentId n
:<|> pure (panic "not implemented yet") -- TODO use patch map to update what we need
-------------------------------------------------------------------
-- | Node API Types management
......
......@@ -106,8 +106,10 @@ get [] = pure []
get pwd = runOpaQuery $ selectNodesWithParentID (last pwd)
-- | Home, need to filter with UserId
{-
home :: Cmd err PWD
home = map _node_id <$> getNodesWithParentId 0 Nothing
-}
-- | ls == get Children
ls :: PWD -> Cmd err [Node HyperdataAny]
......
......@@ -333,8 +333,10 @@ getNodesWith parentId _ nodeType maybeOffset maybeLimit =
-- TODO: Why is the second parameter ignored?
-- TODO: Why not use getNodesWith?
getNodesWithParentId :: NodeId -> Maybe Text -> Cmd err [Node HyperdataAny]
getNodesWithParentId n _ = runOpaQuery $ selectNodesWithParentID n
getNodesWithParentId :: (Hyperdata a, QueryRunnerColumnDefault PGJsonb a)
=> NodeId
-> Cmd err [Node a]
getNodesWithParentId n = runOpaQuery $ selectNodesWithParentID n
------------------------------------------------------------------------
getDocumentsV3WithParentId :: NodeId -> Cmd err [Node HyperdataDocumentV3]
......
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