2 import Gargantext.Database.Prelude (Cmd, runPGSQuery)
3 Module : Gargantext.Database.Query.Table.Node
4 Description : Main Tools of Node to the database
5 Copyright : (c) CNRS, 2017-Present
6 License : AGPL + CECILL v3
7 Maintainer : team@gargantext.org
8 Stability : experimental
12 {-# OPTIONS_GHC -fno-warn-name-shadowing #-}
13 {-# OPTIONS_GHC -fno-warn-orphans #-}
15 {-# LANGUAGE Arrows #-}
16 {-# LANGUAGE ConstraintKinds #-}
17 {-# LANGUAGE FunctionalDependencies #-}
18 {-# LANGUAGE TemplateHaskell #-}
19 {-# LANGUAGE TypeFamilies #-}
21 module Gargantext.Database.Query.Table.Node
24 import Control.Arrow (returnA)
25 import Control.Lens (set, view)
27 import Data.Maybe (Maybe(..))
28 import Data.Text (Text)
29 import GHC.Int (Int64)
30 import Opaleye hiding (FromField)
31 import Opaleye.Internal.QueryArr (Query)
32 import Prelude hiding (null, id, map, sum)
34 import Gargantext.Core.Types
35 import Gargantext.Database.Query.Filter (limit', offset')
36 import Gargantext.Database.Admin.Config (nodeTypeId)
37 import Gargantext.Database.Query.Table.Node.Error
38 import Gargantext.Database.Admin.Types.Hyperdata
39 import Gargantext.Database.Admin.Types.Node (NodeType(..))
40 import Gargantext.Database.Prelude
41 import Gargantext.Database.Query.Table.Node.Contact (HyperdataContact(..), arbitraryHyperdataContact)
42 import Gargantext.Database.Schema.Node
43 import Gargantext.Prelude hiding (sum, head)
44 import Gargantext.Viz.Graph (HyperdataGraph(..))
47 queryNodeSearchTable :: Query NodeSearchRead
48 queryNodeSearchTable = queryTable nodeTableSearch
50 selectNode :: Column PGInt4 -> Query NodeRead
51 selectNode id = proc () -> do
52 row <- queryNodeTable -< ()
53 restrict -< _node_id row .== id
56 runGetNodes :: Query NodeRead -> Cmd err [Node HyperdataAny]
57 runGetNodes = runOpaQuery
59 ------------------------------------------------------------------------
60 ------------------------------------------------------------------------
61 -- | order by publication date
62 -- Favorites (Bool), node_ngrams
63 selectNodesWith :: ParentId -> Maybe NodeType
64 -> Maybe Offset -> Maybe Limit -> Query NodeRead
65 selectNodesWith parentId maybeNodeType maybeOffset maybeLimit =
66 --offset' maybeOffset $ limit' maybeLimit $ orderBy (asc (hyperdataDocument_Publication_date . node_hyperdata)) $ selectNodesWith' parentId typeId
67 limit' maybeLimit $ offset' maybeOffset
68 $ orderBy (asc _node_id)
69 $ selectNodesWith' parentId maybeNodeType
71 selectNodesWith' :: ParentId -> Maybe NodeType -> Query NodeRead
72 selectNodesWith' parentId maybeNodeType = proc () -> do
73 node <- (proc () -> do
74 row@(Node _ typeId _ parentId' _ _ _) <- queryNodeTable -< ()
75 restrict -< parentId' .== (pgNodeId parentId)
77 let typeId' = maybe 0 nodeTypeId maybeNodeType
79 restrict -< if typeId' > 0
80 then typeId .== (pgInt4 (typeId' :: Int))
82 returnA -< row ) -< ()
85 deleteNode :: NodeId -> Cmd err Int
86 deleteNode n = mkCmd $ \conn ->
87 fromIntegral <$> runDelete conn nodeTable
88 (\(Node n_id _ _ _ _ _ _) -> n_id .== pgNodeId n)
90 deleteNodes :: [NodeId] -> Cmd err Int
91 deleteNodes ns = mkCmd $ \conn ->
92 fromIntegral <$> runDelete conn nodeTable
93 (\(Node n_id _ _ _ _ _ _) -> in_ ((map pgNodeId ns)) n_id)
95 -- TODO: NodeType should match with `a'
96 getNodesWith :: JSONB a => NodeId -> proxy a -> Maybe NodeType
97 -> Maybe Offset -> Maybe Limit -> Cmd err [Node a]
98 getNodesWith parentId _ nodeType maybeOffset maybeLimit =
99 runOpaQuery $ selectNodesWith parentId nodeType maybeOffset maybeLimit
101 -- TODO: Why is the second parameter ignored?
102 -- TODO: Why not use getNodesWith?
103 getNodesWithParentId :: (Hyperdata a, QueryRunnerColumnDefault PGJsonb a)
106 getNodesWithParentId n = runOpaQuery $ selectNodesWithParentID n'
112 ------------------------------------------------------------------------
113 getDocumentsV3WithParentId :: NodeId -> Cmd err [Node HyperdataDocumentV3]
114 getDocumentsV3WithParentId n = runOpaQuery $ selectNodesWith' n (Just NodeDocument)
116 -- TODO: merge with getDocumentsWithParentId by having a class IsHyperdataDocument
117 getDocumentsWithParentId :: NodeId -> Cmd err [Node HyperdataDocument]
118 getDocumentsWithParentId n = runOpaQuery $ selectNodesWith' n (Just NodeDocument)
120 getListsModelWithParentId :: NodeId -> Cmd err [Node HyperdataListModel]
121 getListsModelWithParentId n = runOpaQuery $ selectNodesWith' n (Just NodeListModel)
123 getCorporaWithParentId :: NodeId -> Cmd err [Node HyperdataCorpus]
124 getCorporaWithParentId n = runOpaQuery $ selectNodesWith' n (Just NodeCorpus)
126 ------------------------------------------------------------------------
127 selectNodesWithParentID :: NodeId -> Query NodeRead
128 selectNodesWithParentID n = proc () -> do
129 row@(Node _ _ _ parent_id _ _ _) <- queryNodeTable -< ()
130 restrict -< parent_id .== (pgNodeId n)
133 selectNodesWithType :: Column PGInt4 -> Query NodeRead
134 selectNodesWithType type_id = proc () -> do
135 row@(Node _ tn _ _ _ _ _) <- queryNodeTable -< ()
136 restrict -< tn .== type_id
139 type JSONB = QueryRunnerColumnDefault PGJsonb
142 getNode :: HasNodeError err => NodeId -> Cmd err (Node Value)
144 maybeNode <- headMay <$> runOpaQuery (selectNode (pgNodeId nId))
146 Nothing -> nodeError (DoesNotExist nId)
149 getNodeWith :: (HasNodeError err, JSONB a)
150 => NodeId -> proxy a -> Cmd err (Node a)
151 getNodeWith nId _ = do
152 maybeNode <- headMay <$> runOpaQuery (selectNode (pgNodeId nId))
154 Nothing -> nodeError (DoesNotExist nId)
158 ------------------------------------------------------------------------
159 nodeContactW :: Maybe Name -> Maybe HyperdataContact
160 -> AnnuaireId -> UserId -> NodeWrite
161 nodeContactW maybeName maybeContact aId =
162 node NodeContact name contact (Just aId)
164 name = maybe "Contact" identity maybeName
165 contact = maybe arbitraryHyperdataContact identity maybeContact
166 ------------------------------------------------------------------------
167 defaultFolder :: HyperdataCorpus
168 defaultFolder = defaultCorpus
172 nodeFolderW :: Maybe Name -> Maybe HyperdataCorpus -> ParentId -> UserId -> NodeWrite
173 nodeFolderW maybeName maybeFolder pid = node NodeFolder name folder (Just pid)
175 name = maybe "Folder" identity maybeName
176 folder = maybe defaultFolder identity maybeFolder
177 ------------------------------------------------------------------------
178 nodeCorpusW :: Maybe Name -> Maybe HyperdataCorpus -> ParentId -> UserId -> NodeWrite
179 nodeCorpusW maybeName maybeCorpus pId = node NodeCorpus name corpus (Just pId)
181 name = maybe "Corpus" identity maybeName
182 corpus = maybe defaultCorpus identity maybeCorpus
183 --------------------------
184 defaultDocument :: HyperdataDocument
185 defaultDocument = hyperdataDocument
187 nodeDocumentW :: Maybe Name -> Maybe HyperdataDocument -> CorpusId -> UserId -> NodeWrite
188 nodeDocumentW maybeName maybeDocument cId = node NodeDocument name doc (Just cId)
190 name = maybe "Document" identity maybeName
191 doc = maybe defaultDocument identity maybeDocument
192 ------------------------------------------------------------------------
193 defaultAnnuaire :: HyperdataAnnuaire
194 defaultAnnuaire = HyperdataAnnuaire (Just "Title") (Just "Description")
196 nodeAnnuaireW :: Maybe Name -> Maybe HyperdataAnnuaire -> ParentId -> UserId -> NodeWrite
197 nodeAnnuaireW maybeName maybeAnnuaire pId = node NodeAnnuaire name annuaire (Just pId)
199 name = maybe "Annuaire" identity maybeName
200 annuaire = maybe defaultAnnuaire identity maybeAnnuaire
202 ------------------------------------------------------------------------
205 class IsNodeDb a where
209 instance IsNodeDb NodeType where
212 instance HasHyperdata NodeType where
213 data Hyper NodeType = HyperList HyperdataList
214 | HyperCorpus HyperdataCorpus
216 hasHyperdata nt = case nt of
217 NodeList -> HyperList $ HyperdataList (Just "list")
219 unHyper h = case h of
225 class HasDefault a where
226 hasDefaultData :: a -> HyperData
227 hasDefaultName :: a -> Text
229 instance HasDefault NodeType where
230 hasDefaultData nt = case nt of
231 NodeTexts -> HyperdataTexts (Just "Preferences")
232 NodeList -> HyperdataList' (Just "Preferences")
233 NodeListCooc -> HyperdataList' (Just "Preferences")
234 -- NodeFolder -> defaultFolder
235 NodeDashboard -> arbitraryDashboard
236 _ -> panic "HasDefaultData undefined"
237 --NodeAnnuaire -> HyperdataAnnuaire (Just "Title") (Just "Description")
239 hasDefaultName nt = case nt of
242 NodeListCooc -> "Cooc"
244 _ -> panic "HasDefaultName undefined"
246 ------------------------------------------------------------------------
247 nodeDefault :: NodeType -> ParentId -> UserId -> NodeWrite
248 nodeDefault nt parent = node nt name hyper (Just parent)
250 name = (hasDefaultName nt)
251 hyper = (hasDefaultData nt)
253 ------------------------------------------------------------------------
254 arbitraryListModel :: HyperdataListModel
255 arbitraryListModel = HyperdataListModel (400,500) "data/models/test.model" (Just 0.83)
257 mkListModelNode :: HasNodeError err => ParentId -> UserId -> Cmd err [NodeId]
258 mkListModelNode p u = insertNodesR [nodeListModelW Nothing Nothing p u]
260 nodeListModelW :: Maybe Name -> Maybe HyperdataListModel -> ParentId -> UserId -> NodeWrite
261 nodeListModelW maybeName maybeListModel pId = node NodeListModel name list (Just pId)
263 name = maybe "List Model" identity maybeName
264 list = maybe arbitraryListModel identity maybeListModel
266 ------------------------------------------------------------------------
267 arbitraryGraph :: HyperdataGraph
268 arbitraryGraph = HyperdataGraph Nothing
270 nodeGraphW :: Maybe Name -> Maybe HyperdataGraph -> ParentId -> UserId -> NodeWrite
271 nodeGraphW maybeName maybeGraph pId = node NodeGraph name graph (Just pId)
273 name = maybe "Graph" identity maybeName
274 graph = maybe arbitraryGraph identity maybeGraph
276 mkGraph :: ParentId -> UserId -> Cmd err [GraphId]
277 mkGraph p u = insertNodesR [nodeGraphW Nothing Nothing p u]
279 insertGraph :: ParentId -> UserId -> HyperdataGraph -> Cmd err [GraphId]
280 insertGraph p u h = insertNodesR [nodeGraphW Nothing (Just h) p u]
282 ------------------------------------------------------------------------
283 arbitraryDashboard :: HyperData
284 arbitraryDashboard = HyperdataDashboard (Just "Preferences") []
285 ------------------------------------------------------------------------
287 node :: (ToJSON a, Hyperdata a)
294 node nodeType name hyperData parentId userId =
298 (pgNodeId <$> parentId)
301 (pgJSONB $ cs $ encode hyperData)
303 typeId = nodeTypeId nodeType
305 -------------------------------
306 insertNodes :: [NodeWrite] -> Cmd err Int64
307 insertNodes ns = mkCmd $ \conn -> runInsert_ conn $ Insert nodeTable ns rCount Nothing
309 insertNodesR :: [NodeWrite] -> Cmd err [NodeId]
310 insertNodesR ns = mkCmd $ \conn ->
311 runInsert_ conn (Insert nodeTable ns (rReturning (\(Node i _ _ _ _ _ _) -> i)) Nothing)
313 insertNodesWithParent :: Maybe ParentId -> [NodeWrite] -> Cmd err Int64
314 insertNodesWithParent pid ns = insertNodes (set node_parentId (pgNodeId <$> pid) <$> ns)
316 insertNodesWithParentR :: Maybe ParentId -> [NodeWrite] -> Cmd err [NodeId]
317 insertNodesWithParentR pid ns = insertNodesR (set node_parentId (pgNodeId <$> pid) <$> ns)
318 ------------------------------------------------------------------------
319 -- TODO Hierachy of Nodes
320 -- post and get same types Node' and update if changes
322 {- TODO semantic to achieve
323 post c uid pid [ Node' NodeCorpus "name" "{}" []
324 , Node' NodeFolder "name" "{}" [Node' NodeCorpus "test 2" "" [ Node' NodeDocument "title" "metaData" []
325 , Node' NodeDocument "title" "jsonData" []
330 ------------------------------------------------------------------------
333 -- currently this function removes the child relation
334 -- needs a Temporary type between Node' and NodeWriteT
336 node2table :: UserId -> Maybe ParentId -> Node' -> NodeWrite
337 node2table uid pid (Node' nt txt v []) = Node Nothing (pgInt4 $ nodeTypeId nt) (pgInt4 uid) (fmap pgNodeId pid) (pgStrictText txt) Nothing (pgStrictJSONB $ cs $ encode v)
338 node2table _ _ (Node' _ _ _ _) = panic "node2table: should not happen, Tree insert not implemented yet"
341 data Node' = Node' { _n_type :: NodeType
344 , _n_children :: [Node']
347 mkNodes :: [NodeWrite] -> Cmd err Int64
348 mkNodes ns = mkCmd $ \conn -> runInsert_ conn
349 $ Insert nodeTable ns rCount Nothing
351 mkNodeR :: [NodeWrite] -> Cmd err [NodeId]
352 mkNodeR ns = mkCmd $ \conn -> runInsert_ conn $ Insert nodeTable ns (rReturning _node_id) Nothing
354 ------------------------------------------------------------------------
357 data NewNode = NewNode { _newNodeId :: NodeId
358 , _newNodeChildren :: [NodeId] }
360 postNode :: HasNodeError err
366 postNode uid pid (Node' nt txt v []) = do
367 pids <- mkNodeR [node2table uid pid (Node' nt txt v [])]
369 [pid'] -> pure $ NewNode pid' []
370 _ -> nodeError ManyParents
372 postNode uid pid (Node' NodeCorpus txt v ns) = do
373 NewNode pid' _ <- postNode uid pid (Node' NodeCorpus txt v [])
374 pids <- mkNodeR (concat $ map (\n -> [childWith uid pid' n]) ns)
375 pure $ NewNode pid' pids
377 postNode uid pid (Node' NodeAnnuaire txt v ns) = do
378 NewNode pid' _ <- postNode uid pid (Node' NodeAnnuaire txt v [])
379 pids <- mkNodeR (concat $ map (\n -> [childWith uid pid' n]) ns)
380 pure $ NewNode pid' pids
382 postNode uid pid (Node' NodeDashboard txt v ns) = do
383 NewNode pid' _ <- postNode uid pid (Node' NodeDashboard txt v [])
384 pids <- mkNodeR (concat $ map (\n -> [childWith uid pid' n]) ns)
385 pure $ NewNode pid' pids
387 postNode _ _ (Node' _ _ _ _) = nodeError NotImplYet
390 childWith :: UserId -> ParentId -> Node' -> NodeWrite
391 childWith uId pId (Node' NodeDocument txt v []) = node2table uId (Just pId) (Node' NodeDocument txt v [])
392 childWith uId pId (Node' NodeContact txt v []) = node2table uId (Just pId) (Node' NodeContact txt v [])
393 childWith _ _ (Node' _ _ _ _) = panic "This NodeType can not be a child"
396 -- =================================================================== --
398 -- CorpusDocument is a corpus made from a set of documents
399 -- CorpusContact is a corpus made from a set of contacts (syn of Annuaire)
400 data CorpusType = CorpusDocument | CorpusContact
404 mk :: Maybe Name -> Maybe a -> ParentId -> UserId -> Cmd err [NodeId]
406 instance MkCorpus HyperdataCorpus
408 mk n h p u = insertNodesR [nodeCorpusW n h p u]
411 instance MkCorpus HyperdataAnnuaire
413 mk n h p u = insertNodesR [nodeAnnuaireW n h p u]
416 getOrMkList :: HasNodeError err
420 getOrMkList pId uId =
421 maybe (mkList' pId uId) (pure . view node_id) . headMay =<< getListsWithParentId pId
423 mkList' pId uId = maybe (nodeError MkNode) pure . headMay =<< mkNode NodeList pId uId
425 mkList :: HasNodeError err
429 mkList pId uId = mkNode NodeList pId uId
431 -- | TODO remove defaultList
432 defaultList :: HasNodeError err => CorpusId -> Cmd err ListId
434 maybe (nodeError NoListFound) (pure . view node_id) . headMay =<< getListsWithParentId cId
436 mkNode :: NodeType -> ParentId -> UserId -> Cmd err [NodeId]
437 mkNode nt p u = insertNodesR [nodeDefault nt p u]
439 mkDashboard :: ParentId -> UserId -> Cmd err [NodeId]
440 mkDashboard p u = insertNodesR [nodeDashboardW Nothing Nothing p u]
442 nodeDashboardW :: Maybe Name -> Maybe HyperData -> ParentId -> UserId -> NodeWrite
443 nodeDashboardW maybeName maybeDashboard pId = node NodeDashboard name dashboard (Just pId)
445 name = maybe "Board" identity maybeName
446 dashboard = maybe arbitraryDashboard identity maybeDashboard
448 getListsWithParentId :: NodeId -> Cmd err [Node HyperdataList]
449 getListsWithParentId n = runOpaQuery $ selectNodesWith' n (Just NodeList)
451 -- import Gargantext.Database.Node.UpdateOpaleye (updateHyperdata)
452 -- updateNodeUser_fake :: NodeId -> Cmd err Int64
453 -- updateNodeUser_fake n = updateHyperdata n fake_HyperdataUser