Commit 0404bc88 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[FEAT] search in Trash

parent 3fbdae6f
Pipeline #538 failed with stage
...@@ -101,7 +101,7 @@ searchPairs pId (SearchQuery q) o l order = ...@@ -101,7 +101,7 @@ searchPairs pId (SearchQuery q) o l order =
searchDocs :: NodeId -> GargServer SearchDocsAPI searchDocs :: NodeId -> GargServer SearchDocsAPI
searchDocs nId (SearchQuery q) o l order = searchDocs nId (SearchQuery q) o l order =
SearchDocResults <$> searchInCorpus nId q o l order SearchDocResults <$> searchInCorpus nId False q o l order
--SearchResults <$> searchInCorpusWithContacts nId q o l order --SearchResults <$> searchInCorpusWithContacts nId q o l order
...@@ -84,8 +84,8 @@ instance Arbitrary TableQuery where ...@@ -84,8 +84,8 @@ instance Arbitrary TableQuery where
tableApi :: NodeId -> TableQuery -> Cmd err [FacetDoc] tableApi :: NodeId -> TableQuery -> Cmd err [FacetDoc]
tableApi cId (TableQuery o l order ft "") = getTable cId (Just ft) (Just o) (Just l) (Just order) tableApi cId (TableQuery o l order ft "") = getTable cId (Just ft) (Just o) (Just l) (Just order)
tableApi cId (TableQuery o l order ft q) = case ft of tableApi cId (TableQuery o l order ft q) = case ft of
Docs -> searchInCorpus cId [q] (Just o) (Just l) (Just order) Docs -> searchInCorpus cId False [q] (Just o) (Just l) (Just order)
Trash -> panic "TODO search in Trash" -- TODO searchInCorpus cId q o l order Trash -> searchInCorpus cId True [q] (Just o) (Just l) (Just order)
x -> panic $ "not implemented in tableApi " <> (cs $ show x) x -> panic $ "not implemented in tableApi " <> (cs $ show x)
getTable :: NodeId -> Maybe TabType getTable :: NodeId -> Maybe TabType
......
...@@ -123,7 +123,7 @@ fromListTypeId i = lookup i $ fromList [ (listTypeId l, l) | l <- [minBound..max ...@@ -123,7 +123,7 @@ fromListTypeId i = lookup i $ fromList [ (listTypeId l, l) | l <- [minBound..max
-- Queries -- Queries
type Limit = Int type Limit = Int
type Offset = Int type Offset = Int
type IsTrash = Bool
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- All the Database is structred like a hierarchical Tree -- All the Database is structred like a hierarchical Tree
......
...@@ -169,7 +169,6 @@ type FacetDocRead = Facet (Column PGInt4 ) ...@@ -169,7 +169,6 @@ type FacetDocRead = Facet (Column PGInt4 )
----------------------------------------------------------------------- -----------------------------------------------------------------------
----------------------------------------------------------------------- -----------------------------------------------------------------------
type Trash = Bool
data OrderBy = DateAsc | DateDesc data OrderBy = DateAsc | DateDesc
| TitleAsc | TitleDesc | TitleAsc | TitleDesc
| ScoreDesc | ScoreAsc | ScoreDesc | ScoreAsc
...@@ -197,13 +196,13 @@ instance Arbitrary OrderBy ...@@ -197,13 +196,13 @@ instance Arbitrary OrderBy
arbitrary = elements [minBound..maxBound] arbitrary = elements [minBound..maxBound]
runViewAuthorsDoc :: ContactId -> Trash -> Maybe Offset -> Maybe Limit -> Maybe OrderBy -> Cmd err [FacetDoc] runViewAuthorsDoc :: ContactId -> IsTrash -> Maybe Offset -> Maybe Limit -> Maybe OrderBy -> Cmd err [FacetDoc]
runViewAuthorsDoc cId t o l order = runOpaQuery $ filterWith o l order $ viewAuthorsDoc cId t ntId runViewAuthorsDoc cId t o l order = runOpaQuery $ filterWith o l order $ viewAuthorsDoc cId t ntId
where where
ntId = NodeDocument ntId = NodeDocument
-- TODO add delete ? -- TODO add delete ?
viewAuthorsDoc :: ContactId -> Trash -> NodeType -> Query FacetDocRead viewAuthorsDoc :: ContactId -> IsTrash -> NodeType -> Query FacetDocRead
viewAuthorsDoc cId _ nt = proc () -> do viewAuthorsDoc cId _ nt = proc () -> do
(doc,(_,(_,(_,contact)))) <- queryAuthorsDoc -< () (doc,(_,(_,(_,contact)))) <- queryAuthorsDoc -< ()
...@@ -237,13 +236,13 @@ queryAuthorsDoc = leftJoin5 queryNodeTable queryNodeNgramTable queryNgramsTable ...@@ -237,13 +236,13 @@ queryAuthorsDoc = leftJoin5 queryNodeTable queryNodeNgramTable queryNgramsTable
------------------------------------------------------------------------ ------------------------------------------------------------------------
runViewDocuments :: CorpusId -> Trash -> Maybe Offset -> Maybe Limit -> Maybe OrderBy -> Cmd err [FacetDoc] runViewDocuments :: CorpusId -> IsTrash -> Maybe Offset -> Maybe Limit -> Maybe OrderBy -> Cmd err [FacetDoc]
runViewDocuments cId t o l order = runViewDocuments cId t o l order =
runOpaQuery $ filterWith o l order $ viewDocuments cId t ntId runOpaQuery $ filterWith o l order $ viewDocuments cId t ntId
where where
ntId = nodeTypeId NodeDocument ntId = nodeTypeId NodeDocument
viewDocuments :: CorpusId -> Trash -> NodeTypeId -> Query FacetDocRead viewDocuments :: CorpusId -> IsTrash -> NodeTypeId -> Query FacetDocRead
viewDocuments cId t ntId = proc () -> do viewDocuments cId t ntId = proc () -> do
n <- queryNodeTable -< () n <- queryNodeTable -< ()
nn <- queryNodeNodeTable -< () nn <- queryNodeNodeTable -< ()
......
...@@ -22,6 +22,7 @@ Portability : POSIX ...@@ -22,6 +22,7 @@ Portability : POSIX
{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE RankNTypes #-} {-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
module Gargantext.Database.Schema.Node where module Gargantext.Database.Schema.Node where
...@@ -435,6 +436,28 @@ nodeAnnuaireW maybeName maybeAnnuaire pId = node NodeAnnuaire name annuaire (Jus ...@@ -435,6 +436,28 @@ nodeAnnuaireW maybeName maybeAnnuaire pId = node NodeAnnuaire name annuaire (Jus
------------------------------------------------------------------------ ------------------------------------------------------------------------
{-
class IsNodeDb a where
data Node'' a :: *
data Hyper a :: *
instance IsNodeDb NodeType where
data
instance HasHyperdata NodeType where
data Hyper NodeType = HyperList HyperdataList
| HyperCorpus HyperdataCorpus
hasHyperdata nt = case nt of
NodeList -> HyperList $ HyperdataList (Just "list")
unHyper h = case h of
HyperList h' -> h'
--}
class HasDefault a where class HasDefault a where
hasDefaultData :: a -> HyperData hasDefaultData :: a -> HyperData
hasDefaultName :: a -> Text hasDefaultName :: a -> Text
...@@ -452,6 +475,7 @@ instance HasDefault NodeType where ...@@ -452,6 +475,7 @@ instance HasDefault NodeType where
_ -> undefined _ -> undefined
------------------------------------------------------------------------ ------------------------------------------------------------------------
nodeDefault :: NodeType -> ParentId -> UserId -> NodeWrite nodeDefault :: NodeType -> ParentId -> UserId -> NodeWrite
nodeDefault nt parent = node nt name hyper (Just parent) nodeDefault nt parent = node nt name hyper (Just parent)
where where
...@@ -499,6 +523,7 @@ arbitraryDashboard :: HyperdataDashboard ...@@ -499,6 +523,7 @@ arbitraryDashboard :: HyperdataDashboard
arbitraryDashboard = HyperdataDashboard (Just "Preferences") arbitraryDashboard = HyperdataDashboard (Just "Preferences")
------------------------------------------------------------------------ ------------------------------------------------------------------------
node :: (ToJSON a, Hyperdata a) => NodeType -> Name -> a -> Maybe ParentId -> UserId -> NodeWrite node :: (ToJSON a, Hyperdata a) => NodeType -> Name -> a -> Maybe ParentId -> UserId -> NodeWrite
node nodeType name hyperData parentId userId = Node Nothing (pgInt4 typeId) (pgInt4 userId) (pgNodeId <$> parentId) (pgStrictText name) Nothing (pgJSONB $ cs $ encode hyperData) node nodeType name hyperData parentId userId = Node Nothing (pgInt4 typeId) (pgInt4 userId) (pgNodeId <$> parentId) (pgStrictText name) Nothing (pgJSONB $ cs $ encode hyperData)
where where
......
...@@ -56,16 +56,18 @@ queryInDatabase _ q = proc () -> do ...@@ -56,16 +56,18 @@ queryInDatabase _ q = proc () -> do
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- | todo add limit and offset and order -- | todo add limit and offset and order
searchInCorpus :: CorpusId -> [Text] -> Maybe Offset -> Maybe Limit -> Maybe OrderBy -> Cmd err [FacetDoc] searchInCorpus :: CorpusId -> IsTrash -> [Text] -> Maybe Offset -> Maybe Limit -> Maybe OrderBy -> Cmd err [FacetDoc]
searchInCorpus cId q o l order = runOpaQuery (filterWith o l order $ queryInCorpus cId q') searchInCorpus cId t q o l order = runOpaQuery (filterWith o l order $ queryInCorpus cId t q')
where where
q' = intercalate " | " $ map stemIt q q' = intercalate " | " $ map stemIt q
queryInCorpus :: CorpusId -> Text -> O.Query FacetDocRead queryInCorpus :: CorpusId -> IsTrash -> Text -> O.Query FacetDocRead
queryInCorpus cId q = proc () -> do queryInCorpus cId t q = proc () -> do
(n, nn) <- joinInCorpus -< () (n, nn) <- joinInCorpus -< ()
restrict -< ( nn_node1_id nn) .== (toNullable $ pgNodeId cId) restrict -< ( nn_node1_id nn) .== (toNullable $ pgNodeId cId)
restrict -< ( nn_category nn) .>= (toNullable $ pgInt4 1) restrict -< if t
then ( nn_category nn) .== (toNullable $ pgInt4 0)
else ( nn_category nn) .>= (toNullable $ pgInt4 1)
restrict -< (_ns_search n) @@ (pgTSQuery (unpack q)) restrict -< (_ns_search n) @@ (pgTSQuery (unpack q))
restrict -< (_ns_typename n) .== (pgInt4 $ nodeTypeId NodeDocument) restrict -< (_ns_typename n) .== (pgInt4 $ nodeTypeId NodeDocument)
returnA -< FacetDoc (_ns_id n) (_ns_date n) (_ns_name n) (_ns_hyperdata n) (pgInt4 1) (pgInt4 1) returnA -< FacetDoc (_ns_id n) (_ns_date n) (_ns_name n) (_ns_hyperdata n) (pgInt4 1) (pgInt4 1)
......
...@@ -434,7 +434,7 @@ $(deriveJSON (unPrefix "hyperdataNotebook_") ''HyperdataNotebook) ...@@ -434,7 +434,7 @@ $(deriveJSON (unPrefix "hyperdataNotebook_") ''HyperdataNotebook)
instance Hyperdata HyperdataNotebook instance Hyperdata HyperdataNotebook
-- | TODO CLEAN
data HyperData = HyperdataTexts { hd_texts :: Maybe Text } data HyperData = HyperdataTexts { hd_texts :: Maybe Text }
| HyperdataList' { hd_lists :: Maybe Text} | HyperdataList' { hd_lists :: Maybe Text}
deriving (Show, Generic) deriving (Show, Generic)
......
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