Commit 4097d4fe authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

[API] attempt to implement node count in API

parent 7f6848cd
...@@ -55,6 +55,7 @@ import Gargantext.API.Ngrams.NTree (MyTree) ...@@ -55,6 +55,7 @@ import Gargantext.API.Ngrams.NTree (MyTree)
import Gargantext.API.Search (SearchDocsAPI, searchDocs) import Gargantext.API.Search (SearchDocsAPI, searchDocs)
import Gargantext.API.Table import Gargantext.API.Table
import Gargantext.API.Types import Gargantext.API.Types
import Gargantext.Core.Types (NodeTableResult(..))
import Gargantext.Core.Types.Main (Tree, NodeTree, ListType) import Gargantext.Core.Types.Main (Tree, NodeTree, ListType)
import Gargantext.Database.Config (nodeTypeId) import Gargantext.Database.Config (nodeTypeId)
import Gargantext.Database.Facet (FacetDoc, OrderBy(..)) import Gargantext.Database.Facet (FacetDoc, OrderBy(..))
...@@ -158,7 +159,8 @@ type ChildrenApi a = Summary " Summary children" ...@@ -158,7 +159,8 @@ type ChildrenApi a = Summary " Summary children"
:> QueryParam "type" NodeType :> QueryParam "type" NodeType
:> QueryParam "offset" Int :> QueryParam "offset" Int
:> QueryParam "limit" Int :> QueryParam "limit" Int
:> Get '[JSON] [Node a] -- :> Get '[JSON] [Node a]
:> Get '[JSON] (NodeTableResult (Node a))
------------------------------------------------------------------------ ------------------------------------------------------------------------
type NodeNodeAPI a = Get '[JSON] (Node a) type NodeNodeAPI a = Get '[JSON] (Node a)
......
...@@ -22,6 +22,7 @@ module Gargantext.Core.Types ( module Gargantext.Core.Types.Main ...@@ -22,6 +22,7 @@ module Gargantext.Core.Types ( module Gargantext.Core.Types.Main
, Label, Stems , Label, Stems
, HasInvalidError(..), assertValid , HasInvalidError(..), assertValid
, Name , Name
, NodeTableResult(..)
) where ) where
import Control.Lens (Prism', (#)) import Control.Lens (Prism', (#))
...@@ -135,3 +136,8 @@ assertValid :: (MonadError e m, HasInvalidError e) => Validation -> m () ...@@ -135,3 +136,8 @@ assertValid :: (MonadError e m, HasInvalidError e) => Validation -> m ()
assertValid v = when (not $ validationIsValid v) $ throwError $ _InvalidError # v assertValid v = when (not $ validationIsValid v) $ throwError $ _InvalidError # v
-- assertValid :: MonadIO m => Validation -> m () -- assertValid :: MonadIO m => Validation -> m ()
-- assertValid v = when (not $ validationIsValid v) $ fail $ show v -- assertValid v = when (not $ validationIsValid v) $ fail $ show v
data NodeTableResult a = NodeTableResult { tr_count :: Int
, tr_docs :: [a]
} deriving (Generic)
...@@ -30,7 +30,6 @@ import Gargantext.Database.Node.Contact (HyperdataContact) ...@@ -30,7 +30,6 @@ import Gargantext.Database.Node.Contact (HyperdataContact)
import Gargantext.Database.Schema.Node (pgNodeId) import Gargantext.Database.Schema.Node (pgNodeId)
import Control.Arrow (returnA) import Control.Arrow (returnA)
getAllDocuments :: ParentId -> Cmd err [Node HyperdataDocument] getAllDocuments :: ParentId -> Cmd err [Node HyperdataDocument]
getAllDocuments pId = getAllChildren pId (Proxy :: Proxy HyperdataDocument) getAllDocuments pId = getAllChildren pId (Proxy :: Proxy HyperdataDocument)
(Just NodeDocument) (Just NodeDocument)
...@@ -52,11 +51,17 @@ getChildren :: JSONB a ...@@ -52,11 +51,17 @@ getChildren :: JSONB a
-> Maybe NodeType -> Maybe NodeType
-> Maybe Offset -> Maybe Offset
-> Maybe Limit -> Maybe Limit
-> Cmd err [Node a] -> Cmd err (NodeTableResult a)
getChildren pId _ maybeNodeType maybeOffset maybeLimit = runOpaQuery getChildren pId _ maybeNodeType maybeOffset maybeLimit = do
$ limit' maybeLimit $ offset' maybeOffset docs <- runOpaQuery
$ orderBy (asc _node_id) $ limit' maybeLimit $ offset' maybeOffset
$ selectChildren pId maybeNodeType $ orderBy (asc _node_id)
$ selectChildren pId maybeNodeType
allDocs <- runOpaQuery
$ limit' Nothing $ offset' Nothing
$ selectChildren pId maybeNodeType
pure $ NodeTableResult { tr_docs = docs, tr_count = (length allDocs) }
selectChildren :: ParentId selectChildren :: ParentId
-> Maybe NodeType -> Maybe NodeType
......
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