Commit 8cdb7c22 authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

[table] implement querystring params

Limit, offset, search string, order by.
parent 1512855c
...@@ -56,6 +56,11 @@ import Gargantext.Prelude ...@@ -56,6 +56,11 @@ import Gargantext.Prelude
type TableApi = Summary "Table API" type TableApi = Summary "Table API"
:> QueryParam "tabType" TabType :> QueryParam "tabType" TabType
:> QueryParam "list" ListId
:> QueryParam "limit" Int
:> QueryParam "offset" Int
:> QueryParam "orderBy" OrderBy
:> QueryParam "query" Text
:> Get '[JSON] (HashedResponse FacetTableResult) :> Get '[JSON] (HashedResponse FacetTableResult)
:<|> Summary "Table API (POST)" :<|> Summary "Table API (POST)"
:> ReqBody '[JSON] TableQuery :> ReqBody '[JSON] TableQuery
...@@ -90,14 +95,21 @@ tableApi id' = getTableApi id' ...@@ -90,14 +95,21 @@ tableApi id' = getTableApi id'
:<|> getTableHashApi id' :<|> getTableHashApi id'
getTableApi :: NodeId -> Maybe TabType -> Cmd err (HashedResponse FacetTableResult) getTableApi :: NodeId
getTableApi cId tabType = do -> Maybe TabType
t <- getTable cId tabType Nothing Nothing Nothing -> Maybe ListId
-> Maybe Int
-> Maybe Int
-> Maybe OrderBy
-> Maybe Text
-> Cmd err (HashedResponse FacetTableResult)
getTableApi cId tabType _mListId mLimit mOffset mOrderBy mQuery = do
printDebug "[getTableApi] mQuery" mQuery
t <- getTable cId tabType mOffset mLimit mOrderBy mQuery
pure $ constructHashedResponse t pure $ constructHashedResponse t
postTableApi :: NodeId -> TableQuery -> Cmd err FacetTableResult postTableApi :: NodeId -> TableQuery -> Cmd err FacetTableResult
postTableApi cId (TableQuery o l order ft "") = getTable cId (Just ft) (Just o) (Just l) (Just order) postTableApi cId (TableQuery o l order ft "") = getTable cId (Just ft) (Just o) (Just l) (Just order) Nothing
postTableApi cId (TableQuery o l order ft q) = case ft of postTableApi cId (TableQuery o l order ft q) = case ft of
Docs -> searchInCorpus' cId False [q] (Just o) (Just l) (Just order) Docs -> searchInCorpus' cId False [q] (Just o) (Just l) (Just order)
Trash -> searchInCorpus' cId True [q] (Just o) (Just l) (Just order) Trash -> searchInCorpus' cId True [q] (Just o) (Just l) (Just order)
...@@ -105,7 +117,7 @@ postTableApi cId (TableQuery o l order ft q) = case ft of ...@@ -105,7 +117,7 @@ postTableApi cId (TableQuery o l order ft q) = case ft of
getTableHashApi :: NodeId -> Maybe TabType -> Cmd err Text getTableHashApi :: NodeId -> Maybe TabType -> Cmd err Text
getTableHashApi cId tabType = do getTableHashApi cId tabType = do
HashedResponse { hash = h } <- getTableApi cId tabType HashedResponse { hash = h } <- getTableApi cId tabType Nothing Nothing Nothing Nothing Nothing
pure h pure h
searchInCorpus' :: CorpusId searchInCorpus' :: CorpusId
...@@ -121,21 +133,29 @@ searchInCorpus' cId t q o l order = do ...@@ -121,21 +133,29 @@ searchInCorpus' cId t q o l order = do
pure $ TableResult { tr_docs = docs, tr_count = countAllDocs } pure $ TableResult { tr_docs = docs, tr_count = countAllDocs }
getTable :: NodeId -> Maybe TabType getTable :: NodeId
-> Maybe Offset -> Maybe Limit -> Maybe TabType
-> Maybe OrderBy -> Cmd err FacetTableResult -> Maybe Offset
getTable cId ft o l order = do -> Maybe Limit
docs <- getTable' cId ft o l order -> Maybe OrderBy
docsCount <- runCountDocuments cId (if ft == Just Trash then True else False) -> Maybe Text
-> Cmd err FacetTableResult
getTable cId ft o l order query = do
docs <- getTable' cId ft o l order query
docsCount <- runCountDocuments cId (if ft == Just Trash then True else False) query
pure $ TableResult { tr_docs = docs, tr_count = docsCount } pure $ TableResult { tr_docs = docs, tr_count = docsCount }
getTable' :: NodeId -> Maybe TabType getTable' :: NodeId
-> Maybe Offset -> Maybe Limit -> Maybe TabType
-> Maybe OrderBy -> Cmd err [FacetDoc] -> Maybe Offset
getTable' cId ft o l order = -> Maybe Limit
-> Maybe OrderBy
-> Maybe Text
-> Cmd err [FacetDoc]
getTable' cId ft o l order query =
case ft of case ft of
(Just Docs) -> runViewDocuments cId False o l order (Just Docs) -> runViewDocuments cId False o l order query
(Just Trash) -> runViewDocuments cId True o l order (Just Trash) -> runViewDocuments cId True o l order query
(Just MoreFav) -> moreLike cId o l order IsFav (Just MoreFav) -> moreLike cId o l order IsFav
(Just MoreTrash) -> moreLike cId o l order IsTrash (Just MoreTrash) -> moreLike cId o l order IsTrash
x -> panic $ "not implemented in getTable: " <> (cs $ show x) x -> panic $ "not implemented in getTable: " <> (cs $ show x)
......
...@@ -42,10 +42,10 @@ getPriors :: FavOrTrash -> CorpusId -> Cmd err (Events Bool) ...@@ -42,10 +42,10 @@ getPriors :: FavOrTrash -> CorpusId -> Cmd err (Events Bool)
getPriors ft cId = do getPriors ft cId = do
docs_fav <- filter (\(FacetDoc _ _ _ _ f _) -> f == Just 2) docs_fav <- filter (\(FacetDoc _ _ _ _ f _) -> f == Just 2)
<$> runViewDocuments cId False Nothing Nothing Nothing <$> runViewDocuments cId False Nothing Nothing Nothing Nothing
docs_trash <- List.take (List.length docs_fav) docs_trash <- List.take (List.length docs_fav)
<$> runViewDocuments cId True Nothing Nothing Nothing <$> runViewDocuments cId True Nothing Nothing Nothing Nothing
let priors = priorEventsWith text (fav2bool ft) ( List.zip (repeat False) docs_fav let priors = priorEventsWith text (fav2bool ft) ( List.zip (repeat False) docs_fav
...@@ -59,7 +59,7 @@ moreLikeWith :: CorpusId -> Maybe Offset -> Maybe Limit -> Maybe OrderBy ...@@ -59,7 +59,7 @@ moreLikeWith :: CorpusId -> Maybe Offset -> Maybe Limit -> Maybe OrderBy
moreLikeWith cId o l order ft priors = do moreLikeWith cId o l order ft priors = do
docs_test <- filter (\(FacetDoc _ _ _ _ f _) -> f == Just 1) docs_test <- filter (\(FacetDoc _ _ _ _ f _) -> f == Just 1)
<$> runViewDocuments cId False o Nothing order <$> runViewDocuments cId False o Nothing order Nothing
let results = map fst let results = map fst
$ filter ((==) (Just $ not $ fav2bool ft) . snd) $ filter ((==) (Just $ not $ fav2bool ft) . snd)
......
...@@ -42,13 +42,11 @@ import Data.Aeson (FromJSON, ToJSON) ...@@ -42,13 +42,11 @@ import Data.Aeson (FromJSON, ToJSON)
import Data.Aeson.TH (deriveJSON) import Data.Aeson.TH (deriveJSON)
import Data.Profunctor.Product.TH (makeAdaptorAndInstance) import Data.Profunctor.Product.TH (makeAdaptorAndInstance)
import Data.Swagger import Data.Swagger
import Data.Text (Text) import qualified Data.Text as T
import Data.Time (UTCTime) import Data.Time (UTCTime)
import Data.Time.Segment (jour) import Data.Time.Segment (jour)
import Data.Typeable (Typeable)
import GHC.Generics (Generic)
import Opaleye import Opaleye
import Prelude hiding (null, id, map, sum, not, read) import Protolude hiding (null, map, sum, not)
import Servant.API import Servant.API
import Test.QuickCheck (elements) import Test.QuickCheck (elements)
import Test.QuickCheck.Arbitrary import Test.QuickCheck.Arbitrary
...@@ -276,19 +274,32 @@ queryAuthorsDoc = leftJoin5 queryNodeTable queryNodeNodeNgramsTable queryNgramsT ...@@ -276,19 +274,32 @@ queryAuthorsDoc = leftJoin5 queryNodeTable queryNodeNodeNgramsTable queryNgramsT
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- TODO-SECURITY check -- TODO-SECURITY check
runViewDocuments :: CorpusId -> IsTrash -> Maybe Offset -> Maybe Limit -> Maybe OrderBy -> Cmd err [FacetDoc] runViewDocuments :: CorpusId
runViewDocuments cId t o l order = -> IsTrash
runOpaQuery $ filterWith o l order $ viewDocuments cId t ntId -> Maybe Offset
-> Maybe Limit
-> Maybe OrderBy
-> Maybe Text
-> Cmd err [FacetDoc]
runViewDocuments cId t o l order query = do
runOpaQuery $ filterWith o l order sqlQuery
where where
ntId = nodeTypeId NodeDocument ntId = nodeTypeId NodeDocument
sqlQuery = viewDocuments cId t ntId query
runCountDocuments :: CorpusId -> IsTrash -> Cmd err Int runCountDocuments :: CorpusId -> IsTrash -> Maybe Text -> Cmd err Int
runCountDocuments cId t = runCountDocuments cId t mQuery = do
runCountOpaQuery $ viewDocuments cId t $ nodeTypeId NodeDocument runCountOpaQuery sqlQuery
where
sqlQuery = viewDocuments cId t (nodeTypeId NodeDocument) mQuery
viewDocuments :: CorpusId -> IsTrash -> NodeTypeId -> Query FacetDocRead viewDocuments :: CorpusId
viewDocuments cId t ntId = proc () -> do -> IsTrash
-> NodeTypeId
-> Maybe Text
-> Query FacetDocRead
viewDocuments cId t ntId mQuery = proc () -> do
n <- queryNodeTable -< () n <- queryNodeTable -< ()
nn <- queryNodeNodeTable -< () nn <- queryNodeNodeTable -< ()
restrict -< n^.node_id .== nn^.nn_node2_id restrict -< n^.node_id .== nn^.nn_node2_id
...@@ -296,6 +307,11 @@ viewDocuments cId t ntId = proc () -> do ...@@ -296,6 +307,11 @@ viewDocuments cId t ntId = proc () -> do
restrict -< n^.node_typename .== (pgInt4 ntId) restrict -< n^.node_typename .== (pgInt4 ntId)
restrict -< if t then nn^.nn_category .== (pgInt4 0) restrict -< if t then nn^.nn_category .== (pgInt4 0)
else nn^.nn_category .>= (pgInt4 1) else nn^.nn_category .>= (pgInt4 1)
let query = (fromMaybe "" mQuery)
iLikeQuery = T.intercalate "" ["%", query, "%"]
restrict -< (n^.node_name) `ilike` (pgStrictText iLikeQuery)
returnA -< FacetDoc (_node_id n) returnA -< FacetDoc (_node_id n)
(_node_date n) (_node_date n)
(_node_name n) (_node_name n)
......
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