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

[API] Favorites + documents (toTrash) routes.

parent ebe23369
...@@ -206,16 +206,13 @@ type GargAPI' = ...@@ -206,16 +206,13 @@ type GargAPI' =
"user" :> Summary "First user endpoint" "user" :> Summary "First user endpoint"
:> Roots :> Roots
-- Node endpoint -- Node endpoint
:<|> "node" :> Summary "Node endpoint" :<|> "node" :> Summary "Node endpoint"
:> Capture "id" Int :> NodeAPI Value :> Capture "id" Int :> NodeAPI Value
-- Corpus endpoint -- Corpus endpoint
:<|> "corpus":> Summary "Corpus endpoint" :<|> "corpus":> Summary "Corpus endpoint"
:> Capture "id" Int :> NodeAPI HyperdataCorpus :> Capture "id" Int :> NodeAPI HyperdataCorpus
-- Corpus endpoint -- Corpus endpoint
:<|> "nodes" :> Summary "Nodes endpoint" :<|> "nodes" :> Summary "Nodes endpoint"
:> ReqBody '[JSON] [Int] :> NodesAPI :> ReqBody '[JSON] [Int] :> NodesAPI
......
...@@ -52,13 +52,13 @@ import Gargantext.Prelude ...@@ -52,13 +52,13 @@ import Gargantext.Prelude
import Gargantext.Database.Types.Node import Gargantext.Database.Types.Node
import Gargantext.Database.Node ( runCmd import Gargantext.Database.Node ( runCmd
, getNodesWithParentId , getNodesWithParentId
, getNode, getNodesWith , getNode, getNodesWith, CorpusId
, deleteNode, deleteNodes, mk, JSONB) , deleteNode, deleteNodes, mk, JSONB)
import qualified Gargantext.Database.Node.Update as U (update, Update(..)) import qualified Gargantext.Database.Node.Update as U (update, Update(..))
import Gargantext.Database.Facet (FacetDoc , runViewDocuments', OrderBy(..) import Gargantext.Database.Facet (FacetDoc , runViewDocuments', OrderBy(..)
,FacetChart) ,FacetChart)
import Gargantext.Database.Tree (treeDB, HasTreeError(..), TreeError(..)) import Gargantext.Database.Tree (treeDB, HasTreeError(..), TreeError(..))
import Gargantext.Database.NodeNode (nodesToFavorite, nodesToTrash)
-- Graph -- Graph
import Gargantext.TextFlow import Gargantext.TextFlow
import Gargantext.Viz.Graph (Graph) import Gargantext.Viz.Graph (Graph)
...@@ -103,6 +103,48 @@ instance Arbitrary PostNode where ...@@ -103,6 +103,48 @@ instance Arbitrary PostNode where
arbitrary = elements [PostNode "Node test" NodeCorpus] arbitrary = elements [PostNode "Node test" NodeCorpus]
------------------------------------------------------------------------ ------------------------------------------------------------------------
type DocsApi = "documents" :> Summary "Docs api"
:> ReqBody '[JSON] Documents
:> Delete '[JSON] [Int]
data Documents = Documents { documents :: [NodeId]}
deriving (Generic)
instance FromJSON Documents
instance ToJSON Documents
instance ToSchema Documents
delDocs :: Connection -> CorpusId -> Documents -> Handler [Int]
delDocs c cId ds = liftIO $ nodesToTrash c
$ map (\n -> (cId, n, True)) $ documents ds
------------------------------------------------------------------------
type FavApi = "favorites" :> Summary "Modify statut"
:> ReqBody '[JSON] Favorites
:> Put '[JSON] [Int]
:<|> Summary "Delete"
:> ReqBody '[JSON] Favorites
:> Delete '[JSON] [Int]
data Favorites = Favorites { favorites :: [NodeId]}
deriving (Generic)
instance FromJSON Favorites
instance ToJSON Favorites
instance ToSchema Favorites
putFav :: Connection -> CorpusId -> Favorites -> Handler [Int]
putFav c cId fs = liftIO $ nodesToFavorite c
$ map (\n -> (cId, n, True)) $ favorites fs
delFav :: Connection -> CorpusId -> Favorites -> Handler [Int]
delFav c cId fs = liftIO $ nodesToFavorite c
$ map (\n -> (cId, n, False)) $ favorites fs
favApi :: Connection -> CorpusId -> (Favorites -> Handler [Int])
:<|> (Favorites -> Handler [Int])
favApi c cId = putFav c cId :<|> delFav c cId
------------------------------------------------------------------------ ------------------------------------------------------------------------
type NodeAPI a = Get '[JSON] (Node a) type NodeAPI a = Get '[JSON] (Node a)
:<|> "rename" :> Summary " RenameNode Node" :<|> "rename" :> Summary " RenameNode Node"
...@@ -118,7 +160,25 @@ type NodeAPI a = Get '[JSON] (Node a) ...@@ -118,7 +160,25 @@ type NodeAPI a = Get '[JSON] (Node a)
:> QueryParam "offset" Int :> QueryParam "offset" Int
:> QueryParam "limit" Int :> QueryParam "limit" Int
:> Get '[JSON] [Node a] :> Get '[JSON] [Node a]
:<|> Summary " Tabs" :> FacetDocAPI :<|> Summary " Tabs" :> FacetDocAPI
-- TODO: make the NodeId type indexed by `a`, then we no longer need the proxy.
nodeAPI :: JSONB a => Connection -> proxy a -> NodeId -> Server (NodeAPI a)
nodeAPI conn p id
= liftIO (getNode conn id p)
:<|> rename conn id
:<|> postNode conn id
:<|> putNode conn id
:<|> deleteNode' conn id
:<|> getNodesWith' conn id p
:<|> getTable conn id
:<|> getChart conn id
:<|> favApi conn id
:<|> delDocs conn id
-- :<|> upload
-- :<|> query
--data FacetFormat = Table | Chart --data FacetFormat = Table | Chart
data FacetType = Docs | Terms | Sources | Authors | Trash data FacetType = Docs | Terms | Sources | Authors | Trash
...@@ -126,8 +186,8 @@ data FacetType = Docs | Terms | Sources | Authors | Trash ...@@ -126,8 +186,8 @@ data FacetType = Docs | Terms | Sources | Authors | Trash
instance FromHttpApiData FacetType instance FromHttpApiData FacetType
where where
parseUrlPiece "Docs" = pure Docs parseUrlPiece "Docs" = pure Docs
parseUrlPiece "Terms" = pure Terms parseUrlPiece "Terms" = pure Terms
parseUrlPiece "Sources" = pure Sources parseUrlPiece "Sources" = pure Sources
parseUrlPiece "Authors" = pure Authors parseUrlPiece "Authors" = pure Authors
parseUrlPiece "Trash" = pure Trash parseUrlPiece "Trash" = pure Trash
...@@ -141,6 +201,7 @@ instance Arbitrary FacetType ...@@ -141,6 +201,7 @@ instance Arbitrary FacetType
where where
arbitrary = elements [minBound .. maxBound] arbitrary = elements [minBound .. maxBound]
------------------------------------------------------------------------
type FacetDocAPI = "table" type FacetDocAPI = "table"
:> Summary " Table data" :> Summary " Table data"
:> QueryParam "view" FacetType :> QueryParam "view" FacetType
...@@ -154,6 +215,8 @@ type FacetDocAPI = "table" ...@@ -154,6 +215,8 @@ type FacetDocAPI = "table"
:> QueryParam "from" UTCTime :> QueryParam "from" UTCTime
:> QueryParam "to" UTCTime :> QueryParam "to" UTCTime
:> Get '[JSON] [FacetChart] :> Get '[JSON] [FacetChart]
:<|> Summary " Favorites" :> FavApi
:<|> Summary " Documents" :> DocsApi
-- Depending on the Type of the Node, we could post -- Depending on the Type of the Node, we could post
-- New documents for a corpus -- New documents for a corpus
...@@ -172,6 +235,7 @@ roots conn = liftIO (putStrLn ( "/user" :: Text) >> getNodesWithParentId 0 Nothi ...@@ -172,6 +235,7 @@ roots conn = liftIO (putStrLn ( "/user" :: Text) >> getNodesWithParentId 0 Nothi
:<|> pure (panic "not implemented yet") -- TODO :<|> pure (panic "not implemented yet") -- TODO
------------------------------------------------------------------------
type GraphAPI = Get '[JSON] Graph type GraphAPI = Get '[JSON] Graph
graphAPI :: Connection -> NodeId -> Server GraphAPI graphAPI :: Connection -> NodeId -> Server GraphAPI
graphAPI _ _ = liftIO $ textFlow (Mono EN) (Contexts contextText) graphAPI _ _ = liftIO $ textFlow (Mono EN) (Contexts contextText)
...@@ -189,19 +253,7 @@ type TreeAPI = Get '[JSON] (Tree NodeTree) ...@@ -189,19 +253,7 @@ type TreeAPI = Get '[JSON] (Tree NodeTree)
treeAPI :: Connection -> NodeId -> Server TreeAPI treeAPI :: Connection -> NodeId -> Server TreeAPI
treeAPI = treeDB treeAPI = treeDB
-- TODO: make the NodeId type indexed by `a`, then we no longer need the proxy. ------------------------------------------------------------------------
nodeAPI :: JSONB a => Connection -> proxy a -> NodeId -> Server (NodeAPI a)
nodeAPI conn p id
= liftIO (getNode conn id p)
:<|> rename conn id
:<|> postNode conn id
:<|> putNode conn id
:<|> deleteNode' conn id
:<|> getNodesWith' conn id p
:<|> getTable conn id
:<|> getChart conn id
-- :<|> upload
-- :<|> query
-- | Check if the name is less than 255 char -- | Check if the name is less than 255 char
--rename :: Connection -> NodeId -> Rename -> Server NodeAPI --rename :: Connection -> NodeId -> Rename -> Server NodeAPI
rename :: Connection -> NodeId -> RenameNode -> Handler [Int] rename :: Connection -> NodeId -> RenameNode -> Handler [Int]
...@@ -210,14 +262,17 @@ rename c nId (RenameNode name) = liftIO $ U.update (U.Rename nId name) c ...@@ -210,14 +262,17 @@ rename c nId (RenameNode name) = liftIO $ U.update (U.Rename nId name) c
nodesAPI :: Connection -> [NodeId] -> Server NodesAPI nodesAPI :: Connection -> [NodeId] -> Server NodesAPI
nodesAPI conn ids = deleteNodes' conn ids nodesAPI conn ids = deleteNodes' conn ids
getTable :: Connection -> NodeId -> Maybe FacetType -> Maybe Offset -> Maybe Limit -> Maybe OrderBy -> Handler [FacetDoc] getTable :: Connection -> NodeId -> Maybe FacetType
-> Maybe Offset -> Maybe Limit
-> Maybe OrderBy -> Handler [FacetDoc]
getTable c cId ft o l order = liftIO $ case ft of getTable c cId ft o l order = liftIO $ case ft of
(Just Docs) -> runViewDocuments' c cId False o l order (Just Docs) -> runViewDocuments' c cId False o l order
(Just Trash) -> runViewDocuments' c cId True o l order (Just Trash) -> runViewDocuments' c cId True o l order
_ -> panic "not implemented" _ -> panic "not implemented"
getChart :: Connection -> NodeId -> Maybe UTCTime -> Maybe UTCTime
-> Handler [FacetChart]
getChart _ _ _ _ = undefined -- TODO
postNode :: Connection -> NodeId -> PostNode -> Handler [Int] postNode :: Connection -> NodeId -> PostNode -> Handler [Int]
postNode c pId (PostNode name nt) = liftIO $ mk c nt (Just pId) name postNode c pId (PostNode name nt) = liftIO $ mk c nt (Just pId) name
...@@ -236,10 +291,6 @@ getNodesWith' :: JSONB a => Connection -> NodeId -> proxy a -> Maybe NodeType ...@@ -236,10 +291,6 @@ getNodesWith' :: JSONB a => Connection -> NodeId -> proxy a -> Maybe NodeType
getNodesWith' conn id p nodeType offset limit = liftIO (getNodesWith conn id p nodeType offset limit) getNodesWith' conn id p nodeType offset limit = liftIO (getNodesWith conn id p nodeType offset limit)
getChart :: Connection -> NodeId -> Maybe UTCTime -> Maybe UTCTime
-> Handler [FacetChart]
getChart _ _ _ _ = undefined -- TODO
query :: Text -> Handler Text query :: Text -> Handler Text
query s = pure s query s = pure s
......
...@@ -96,8 +96,8 @@ instance QueryRunnerColumnDefault PGBool (Maybe Bool) where ...@@ -96,8 +96,8 @@ instance QueryRunnerColumnDefault PGBool (Maybe Bool) where
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- | Favorite management -- | Favorite management
nodeToFavorite :: PGS.Connection -> CorpusId -> DocId -> Bool -> IO [PGS.Only Int] nodeToFavorite :: PGS.Connection -> CorpusId -> DocId -> Bool -> IO [Int]
nodeToFavorite c cId dId b = PGS.query c favQuery (b,cId,dId) nodeToFavorite c cId dId b = map (\(PGS.Only a) -> a) <$> PGS.query c favQuery (b,cId,dId)
where where
favQuery :: PGS.Query favQuery :: PGS.Query
favQuery = [sql|UPDATE nodes_nodes SET favorite = ? favQuery = [sql|UPDATE nodes_nodes SET favorite = ?
...@@ -105,8 +105,9 @@ nodeToFavorite c cId dId b = PGS.query c favQuery (b,cId,dId) ...@@ -105,8 +105,9 @@ nodeToFavorite c cId dId b = PGS.query c favQuery (b,cId,dId)
RETURNING node2_id; RETURNING node2_id;
|] |]
nodesToFavorite :: PGS.Connection -> [(CorpusId,DocId,Bool)] -> IO [PGS.Only Int] nodesToFavorite :: PGS.Connection -> [(CorpusId,DocId,Bool)] -> IO [Int]
nodesToFavorite c inputData = PGS.query c trashQuery (PGS.Only $ Values fields inputData) nodesToFavorite c inputData = map (\(PGS.Only a) -> a)
<$> PGS.query c trashQuery (PGS.Only $ Values fields inputData)
where where
fields = map (\t-> QualifiedIdentifier Nothing t) ["int4","int4","bool"] fields = map (\t-> QualifiedIdentifier Nothing t) ["int4","int4","bool"]
trashQuery :: PGS.Query trashQuery :: PGS.Query
...@@ -131,8 +132,9 @@ nodeToTrash c cId dId b = PGS.query c trashQuery (b,cId,dId) ...@@ -131,8 +132,9 @@ nodeToTrash c cId dId b = PGS.query c trashQuery (b,cId,dId)
|] |]
-- | Trash Massive -- | Trash Massive
nodesToTrash :: PGS.Connection -> [(CorpusId,DocId,Bool)] -> IO [PGS.Only Int] nodesToTrash :: PGS.Connection -> [(CorpusId,DocId,Bool)] -> IO [Int]
nodesToTrash c inputData = PGS.query c trashQuery (PGS.Only $ Values fields inputData) nodesToTrash c inputData = map (\(PGS.Only a) -> a)
<$> PGS.query c trashQuery (PGS.Only $ Values fields inputData)
where where
fields = map (\t-> QualifiedIdentifier Nothing t) ["int4","int4","bool"] fields = map (\t-> QualifiedIdentifier Nothing t) ["int4","int4","bool"]
trashQuery :: PGS.Query trashQuery :: PGS.Query
......
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