Comments about ACCESS and EVENTS

parent 7aa33462
...@@ -248,10 +248,12 @@ type GargAPI' = ...@@ -248,10 +248,12 @@ type GargAPI' =
:> QueryParam "limit" Int :> QueryParam "limit" Int
:> QueryParam "order" OrderBy :> QueryParam "order" OrderBy
:> SearchAPI :> SearchAPI
-- TODO move to NodeAPI?
:<|> "graph" :> Summary "Graph endpoint" :<|> "graph" :> Summary "Graph endpoint"
:> Capture "id" NodeId :> GraphAPI :> Capture "id" NodeId :> GraphAPI
-- TODO move to NodeAPI?
-- Tree endpoint -- Tree endpoint
:<|> "tree" :> Summary "Tree endpoint" :<|> "tree" :> Summary "Tree endpoint"
:> Capture "id" NodeId :> TreeAPI :> Capture "id" NodeId :> TreeAPI
......
...@@ -44,6 +44,8 @@ import Gargantext.Prelude ...@@ -44,6 +44,8 @@ import Gargantext.Prelude
import Gargantext.Core.Utils.Prefix (unPrefix) import Gargantext.Core.Utils.Prefix (unPrefix)
----------------------------------------------------------------------- -----------------------------------------------------------------------
-- TODO-ACCESS: CanCount
-- TODO-EVENTS: No events as this is a read only query.
type CountAPI = Post '[JSON] Counts type CountAPI = Post '[JSON] Counts
----------------------------------------------------------------------- -----------------------------------------------------------------------
......
...@@ -75,7 +75,11 @@ import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary) ...@@ -75,7 +75,11 @@ import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary)
type GargServer api = forall env m. CmdM env ServantErr m => ServerT api m type GargServer api = forall env m. CmdM env ServantErr m => ServerT api m
------------------------------------------------------------------- -------------------------------------------------------------------
-- | TODO : access by admin only -- TODO-ACCESS: access by admin only.
-- At first let's just have an isAdmin check.
-- Later: check userId CanDeleteNodes Nothing
-- TODO-EVENTS: DeletedNodes [NodeId]
-- {"tag": "DeletedNodes", "nodes": [Int*]}
type NodesAPI = Delete '[JSON] Int type NodesAPI = Delete '[JSON] Int
-- | Delete Nodes -- | Delete Nodes
...@@ -85,8 +89,13 @@ nodesAPI :: [NodeId] -> GargServer NodesAPI ...@@ -85,8 +89,13 @@ nodesAPI :: [NodeId] -> GargServer NodesAPI
nodesAPI ids = deleteNodes ids nodesAPI ids = deleteNodes ids
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- | TODO: access by admin only -- | TODO-ACCESS: access by admin only.
-- To manager the Users roots -- At first let's just have an isAdmin check.
-- Later: CanAccessAnyNode or (CanGetAnyNode, CanPutAnyNode)
-- To manage the Users roots
-- TODO-EVENTS:
-- PutNode ?
-- TODO needs design discussion.
type Roots = Get '[JSON] [NodeAny] type Roots = Get '[JSON] [NodeAny]
:<|> Put '[JSON] Int -- TODO :<|> Put '[JSON] Int -- TODO
...@@ -97,10 +106,21 @@ roots = (liftIO (putStrLn ( "/user" :: Text)) >> getNodesWithParentId 0 Nothing) ...@@ -97,10 +106,21 @@ roots = (liftIO (putStrLn ( "/user" :: Text)) >> getNodesWithParentId 0 Nothing)
------------------------------------------------------------------- -------------------------------------------------------------------
-- | Node API Types management -- | Node API Types management
-- TODO : access by users -- TODO-ACCESS : access by users
-- No ownership check is needed if we strictly follow the capability model.
--
-- CanGetNode (Node, Children, TableApi, TableNgramsApiGet, PairingApi, ChartApi,
-- SearchAPI)
-- CanRenameNode (or part of CanEditNode?)
-- CanCreateChildren (PostNodeApi)
-- CanEditNode / CanPutNode TODO not implemented yet
-- CanDeleteNode
-- CanPatch (TableNgramsApi)
-- CanFavorite
-- CanMoveToTrash
type NodeAPI a = Get '[JSON] (Node a) type NodeAPI a = Get '[JSON] (Node a)
:<|> "rename" :> RenameApi :<|> "rename" :> RenameApi
:<|> PostNodeApi :<|> PostNodeApi -- TODO move to children POST
:<|> Put '[JSON] Int :<|> Put '[JSON] Int
:<|> Delete '[JSON] Int :<|> Delete '[JSON] Int
:<|> "children" :> ChildrenApi a :<|> "children" :> ChildrenApi a
...@@ -121,6 +141,8 @@ type NodeAPI a = Get '[JSON] (Node a) ...@@ -121,6 +141,8 @@ type NodeAPI a = Get '[JSON] (Node a)
:> QueryParam "order" OrderBy :> QueryParam "order" OrderBy
:> SearchAPI :> SearchAPI
-- TODO-ACCESS: check userId CanRenameNode nodeId
-- TODO-EVENTS: NodeRenamed RenameNode or re-use some more general NodeEdited...
type RenameApi = Summary " Rename Node" type RenameApi = Summary " Rename Node"
:> ReqBody '[JSON] RenameNode :> ReqBody '[JSON] RenameNode
:> Put '[JSON] [Int] :> Put '[JSON] [Int]
...@@ -248,6 +270,8 @@ type ChartApi = Summary " Chart API" ...@@ -248,6 +270,8 @@ type ChartApi = Summary " Chart API"
-- :<|> "query" :> Capture "string" Text :> Get '[JSON] Text -- :<|> "query" :> Capture "string" Text :> Get '[JSON] Text
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- TODO-ACCESS: CanGetNode
-- TODO-EVENTS: No events as this is a read only query.
type GraphAPI = Get '[JSON] Graph type GraphAPI = Get '[JSON] Graph
graphAPI :: NodeId -> GargServer GraphAPI graphAPI :: NodeId -> GargServer GraphAPI
...@@ -302,6 +326,8 @@ instance HasTreeError ServantErr where ...@@ -302,6 +326,8 @@ instance HasTreeError ServantErr where
mk TooManyRoots = err500 { errBody = e <> "Too many root nodes" } mk TooManyRoots = err500 { errBody = e <> "Too many root nodes" }
type TreeAPI = Get '[JSON] (Tree NodeTree) type TreeAPI = Get '[JSON] (Tree NodeTree)
-- TODO-ACCESS: CanTree or CanGetNode
-- TODO-EVENTS: No events as this is a read only query.
treeAPI :: NodeId -> GargServer TreeAPI treeAPI :: NodeId -> GargServer TreeAPI
treeAPI = treeDB treeAPI = treeDB
......
...@@ -85,6 +85,8 @@ instance ToSchema SearchResults where ...@@ -85,6 +85,8 @@ instance ToSchema SearchResults where
defaultSchemaOptions {fieldLabelModifier = \fieldLabel -> drop 4 fieldLabel} defaultSchemaOptions {fieldLabelModifier = \fieldLabel -> drop 4 fieldLabel}
----------------------------------------------------------------------- -----------------------------------------------------------------------
-- TODO-ACCESS: CanSearch? or is it part of CanGetNode
-- TODO-EVENTS: No event, this is a read-only query.
type SearchAPI = Post '[JSON] SearchResults type SearchAPI = Post '[JSON] SearchResults
----------------------------------------------------------------------- -----------------------------------------------------------------------
......
...@@ -97,7 +97,13 @@ flowInsertAnnuaire name children = do ...@@ -97,7 +97,13 @@ flowInsertAnnuaire name children = do
pure (ids, masterUserId, masterCorpusId, userId, userCorpusId) pure (ids, masterUserId, masterCorpusId, userId, userCorpusId)
-- TODO-ACCESS:
-- check userId CanFillUserCorpus userCorpusId
-- check masterUserId CanFillMasterCorpus masterCorpusId
--
-- TODO-EVENTS:
-- InsertedNgrams ?
-- InsertedNodeNgrams ?
flowCorpus' :: HasNodeError err flowCorpus' :: HasNodeError err
=> NodeType -> [HyperdataDocument] => NodeType -> [HyperdataDocument]
-> ([ReturnId], UserId, CorpusId, UserId, CorpusId) -> ([ReturnId], UserId, CorpusId, UserId, CorpusId)
......
...@@ -113,6 +113,8 @@ import Database.PostgreSQL.Simple (formatQuery) ...@@ -113,6 +113,8 @@ import Database.PostgreSQL.Simple (formatQuery)
data ToDbData = ToDbDocument HyperdataDocument | ToDbContact HyperdataContact data ToDbData = ToDbDocument HyperdataDocument | ToDbContact HyperdataContact
-- TODO-ACCESS: check uId CanInsertDoc pId && checkDocType nodeType
-- TODO-EVENTS: InsertedNodes
insertDocuments :: UserId -> ParentId -> NodeType -> [ToDbData] -> Cmd err [ReturnId] insertDocuments :: UserId -> ParentId -> NodeType -> [ToDbData] -> Cmd err [ReturnId]
insertDocuments uId pId nodeType = insertDocuments uId pId nodeType =
runPGSQuery queryInsert . Only . Values fields . prepare uId pId nodeType runPGSQuery queryInsert . Only . Values fields . prepare uId pId nodeType
......
...@@ -193,9 +193,11 @@ indexNgramsTWith = fmap . indexNgramsWith ...@@ -193,9 +193,11 @@ indexNgramsTWith = fmap . indexNgramsWith
indexNgramsWith :: (NgramsTerms -> NgramsId) -> Ngrams -> NgramsIndexed indexNgramsWith :: (NgramsTerms -> NgramsId) -> Ngrams -> NgramsIndexed
indexNgramsWith f n = NgramsIndexed n (f $ _ngramsTerms n) indexNgramsWith f n = NgramsIndexed n (f $ _ngramsTerms n)
-- TODO-ACCESS: access must not be checked here but when insertNgrams is called.
insertNgrams :: [Ngrams] -> Cmd err (Map NgramsTerms NgramsId) insertNgrams :: [Ngrams] -> Cmd err (Map NgramsTerms NgramsId)
insertNgrams ns = fromList <$> map (\(NgramIds i t) -> (t, i)) <$> (insertNgrams' ns) insertNgrams ns = fromList <$> map (\(NgramIds i t) -> (t, i)) <$> (insertNgrams' ns)
-- TODO-ACCESS: access must not be checked here but when insertNgrams' is called.
insertNgrams' :: [Ngrams] -> Cmd err [NgramIds] insertNgrams' :: [Ngrams] -> Cmd err [NgramIds]
insertNgrams' ns = runPGSQuery queryInsertNgrams (PGS.Only $ Values fields ns) insertNgrams' ns = runPGSQuery queryInsertNgrams (PGS.Only $ Values fields ns)
where where
......
...@@ -288,6 +288,8 @@ data NodeNgramsUpdate = NodeNgramsUpdate ...@@ -288,6 +288,8 @@ data NodeNgramsUpdate = NodeNgramsUpdate
} }
-- TODO wrap these updates in a transaction. -- TODO wrap these updates in a transaction.
-- TODO-ACCESS:
-- * check userId CanUpdateNgrams userListId
updateNodeNgrams :: NodeNgramsUpdate -> Cmd err () updateNodeNgrams :: NodeNgramsUpdate -> Cmd err ()
updateNodeNgrams nnu = do updateNodeNgrams nnu = do
updateNodeNgrams' userListId $ _nnu_lists_update nnu updateNodeNgrams' userListId $ _nnu_lists_update nnu
......
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