Node.hs 15 KB
Newer Older
1
{-|
2
import Gargantext.Database.Prelude (Cmd, runPGSQuery)
3
Module      : Gargantext.Database.Query.Table.Node
4 5 6 7 8 9 10 11 12 13 14 15 16
Description : Main Tools of Node to the database
Copyright   : (c) CNRS, 2017-Present
License     : AGPL + CECILL v3
Maintainer  : team@gargantext.org
Stability   : experimental
Portability : POSIX
-}

{-# OPTIONS_GHC -fno-warn-orphans        #-}

{-# LANGUAGE Arrows                 #-}
{-# LANGUAGE ConstraintKinds        #-}
{-# LANGUAGE FunctionalDependencies #-}
17
{-# LANGUAGE QuasiQuotes       #-}
18 19 20
{-# LANGUAGE TemplateHaskell        #-}
{-# LANGUAGE TypeFamilies           #-}

21
module Gargantext.Database.Query.Table.Node
22
  where
23 24 25 26

import Control.Arrow (returnA)
import Control.Lens (set, view)
import Data.Aeson
27
import Data.Maybe (fromMaybe)
28
import Data.Text (Text)
29 30 31 32
import Database.PostgreSQL.Simple.SqlQQ (sql)
import Opaleye hiding (FromField)
import Prelude hiding (null, id, map, sum)

Alexandre Delanoë's avatar
Alexandre Delanoë committed
33
import Gargantext.Core
34
import Gargantext.Core.Types
35
import Gargantext.Database.Admin.Types.Hyperdata
36
import Gargantext.Database.Admin.Types.Hyperdata.Default
37
import Gargantext.Database.Prelude
38 39
import Gargantext.Database.Query.Filter (limit', offset')
import Gargantext.Database.Query.Table.Node.Error
40 41 42
import Gargantext.Database.Schema.Node
import Gargantext.Prelude hiding (sum, head)

43 44 45
import qualified Database.PostgreSQL.Simple as PGS


46
queryNodeSearchTable :: Select NodeSearchRead
47
queryNodeSearchTable = selectTable nodeTableSearch
48

49
selectNode :: Column SqlInt4 -> Select NodeRead
50
selectNode id' = proc () -> do
51
    row      <- queryNodeTable -< ()
52
    restrict -< _node_id row .== id'
53
    returnA  -< row
54

55
runGetNodes :: Select NodeRead -> Cmd err [Node HyperdataAny]
56 57 58 59 60 61
runGetNodes = runOpaQuery

------------------------------------------------------------------------
------------------------------------------------------------------------
-- | order by publication date
-- Favorites (Bool), node_ngrams
62 63
selectNodesWith :: HasDBid NodeType
                => ParentId     -> Maybe NodeType
64
                -> Maybe Offset -> Maybe Limit   -> Select NodeRead
65
selectNodesWith parentId maybeNodeType maybeOffset maybeLimit =
66 67 68 69 70
        --offset' maybeOffset $ limit' maybeLimit $ orderBy (asc (hyperdataDocument_Publication_date . node_hyperdata)) $ selectNodesWith' parentId typeId
  limit' maybeLimit $ offset' maybeOffset
                    $ orderBy (asc _node_id)
                    $ selectNodesWith' parentId maybeNodeType

71
selectNodesWith' :: HasDBid NodeType
72
                 => ParentId -> Maybe NodeType -> Select NodeRead
73
selectNodesWith' parentId maybeNodeType = proc () -> do
74
    node' <- (proc () -> do
75
      row@(Node _ _ typeId _ parentId' _ _ _) <- queryNodeTable -< ()
76 77
      restrict -< parentId' .== (pgNodeId parentId)

78
      let typeId' = maybe 0 toDBid maybeNodeType
79 80

      restrict -< if typeId' > 0
81
                     then typeId   .== (sqlInt4 (typeId' :: Int))
82
                     else (sqlBool True)
83
      returnA  -< row ) -< ()
84
    returnA -< node'
85 86 87

deleteNode :: NodeId -> Cmd err Int
deleteNode n = mkCmd $ \conn ->
88 89 90 91 92
  fromIntegral <$> runDelete_ conn
                 (Delete nodeTable
                         (\(Node n_id _ _ _ _ _ _ _) -> n_id .== pgNodeId n)
                         rCount
                 )
93 94 95

deleteNodes :: [NodeId] -> Cmd err Int
deleteNodes ns = mkCmd $ \conn ->
96 97 98 99 100
  fromIntegral <$> runDelete_ conn
                   (Delete nodeTable
                           (\(Node n_id _ _ _ _ _ _ _) -> in_ ((map pgNodeId ns)) n_id)
                           rCount
                   )
101 102

-- TODO: NodeType should match with `a'
103
getNodesWith :: (JSONB a, HasDBid NodeType) => NodeId -> proxy a -> Maybe NodeType
104 105 106 107 108 109
             -> Maybe Offset -> Maybe Limit -> Cmd err [Node a]
getNodesWith parentId _ nodeType maybeOffset maybeLimit =
    runOpaQuery $ selectNodesWith parentId nodeType maybeOffset maybeLimit

-- TODO: Why is the second parameter ignored?
-- TODO: Why not use getNodesWith?
110
getNodesWithParentId :: (Hyperdata a, JSONB a)
111 112 113 114 115 116 117 118
                     => Maybe NodeId
                     -> Cmd err [Node a]
getNodesWithParentId n = runOpaQuery $ selectNodesWithParentID n'
  where
    n' = case n of
      Just n'' -> n''
      Nothing  -> 0

119 120 121 122

-- | Given a node id, find it's closest parent of given type
-- NOTE: This isn't too optimal: can make successive queries depending on how
-- deeply nested the child is.
123 124
getClosestParentIdByType :: HasDBid NodeType
                         => NodeId
125 126 127
                         -> NodeType
                         -> Cmd err (Maybe NodeId)
getClosestParentIdByType nId nType = do
128
  result <- runPGSQuery query (PGS.Only nId)
129
  case result of
130
    [(NodeId parentId, pTypename)] -> do
131
      if toDBid nType == pTypename then
132 133 134 135 136
        pure $ Just $ NodeId parentId
      else
        getClosestParentIdByType (NodeId parentId) nType
    _ -> pure Nothing
  where
137
    query :: PGS.Query
138 139
    query = [sql|
      SELECT n2.id, n2.typename
140
      FROM nodes n1
141
        JOIN nodes n2 ON n1.parent_id = n2.id
142
        WHERE n1.id = ?;
143 144
    |]

145 146 147 148 149 150 151
-- | Similar to `getClosestParentIdByType` but includes current node
-- in search too
getClosestParentIdByType' :: HasDBid NodeType
                          => NodeId
                          -> NodeType
                          -> Cmd err (Maybe NodeId)
getClosestParentIdByType' nId nType = do
152
  result <- runPGSQuery query (PGS.Only nId)
153 154 155 156 157 158 159 160
  case result of
    [(NodeId id, pTypename)] -> do
      if toDBid nType == pTypename then
        pure $ Just $ NodeId id
      else
        getClosestParentIdByType nId nType
    _ -> pure Nothing
  where
161
    query :: PGS.Query
162 163 164
    query = [sql|
      SELECT n.id, n.typename
      FROM nodes n
165
      WHERE n.id = ?;
166 167
    |]

168 169 170 171 172 173 174
-- | Given a node id, find all it's children (no matter how deep) of
-- given node type.
getChildrenByType :: HasDBid NodeType
                  => NodeId
                  -> NodeType
                  -> Cmd err [NodeId]
getChildrenByType nId nType = do
175
  result <- runPGSQuery query (PGS.Only nId)
176 177 178
  children_lst <- mapM (\(id, _) -> getChildrenByType id nType) result
  pure $ concat $ [fst <$> filter (\(_, pTypename) -> pTypename == toDBid nType) result] ++ children_lst
  where
179
    query :: PGS.Query
180 181 182
    query = [sql|
      SELECT n.id, n.typename
      FROM nodes n
183
      WHERE n.parent_id = ?;
184 185
    |]

186
------------------------------------------------------------------------
187
getDocumentsV3WithParentId :: HasDBid NodeType => NodeId -> Cmd err [Node HyperdataDocumentV3]
188 189 190
getDocumentsV3WithParentId n = runOpaQuery $ selectNodesWith' n (Just NodeDocument)

-- TODO: merge with getDocumentsWithParentId by having a class IsHyperdataDocument
191
getDocumentsWithParentId :: HasDBid NodeType => NodeId -> Cmd err [Node HyperdataDocument]
192 193
getDocumentsWithParentId n = runOpaQuery $ selectNodesWith' n (Just NodeDocument)

194
getListsModelWithParentId :: HasDBid NodeType => NodeId -> Cmd err [Node HyperdataModel]
195
getListsModelWithParentId n = runOpaQuery $ selectNodesWith' n (Just NodeModel)
196

197
getCorporaWithParentId :: HasDBid NodeType => NodeId -> Cmd err [Node HyperdataCorpus]
198 199 200
getCorporaWithParentId n = runOpaQuery $ selectNodesWith' n (Just NodeCorpus)

------------------------------------------------------------------------
201
selectNodesWithParentID :: NodeId -> Select NodeRead
202
selectNodesWithParentID n = proc () -> do
203
    row@(Node _ _ _ _ parent_id _ _ _) <- queryNodeTable -< ()
204 205 206
    restrict -< parent_id .== (pgNodeId n)
    returnA -< row

207 208 209 210

------------------------------------------------------------------------
-- | Example of use:
-- runCmdReplEasy  (getNodesWithType NodeList (Proxy :: Proxy HyperdataList))
211
getNodesWithType :: (HasNodeError err, JSONB a, HasDBid NodeType) => NodeType -> proxy a -> Cmd err [Node a]
212
getNodesWithType nt _ = runOpaQuery $ selectNodesWithType nt
213
  where
214
    selectNodesWithType ::  HasDBid NodeType
215
                         => NodeType -> Select NodeRead
216
    selectNodesWithType nt' = proc () -> do
217
        row@(Node _ _ tn _ _ _ _ _) <- queryNodeTable -< ()
218
        restrict -< tn .== (sqlInt4 $ toDBid nt')
219 220
        returnA -< row

221
getNodesIdWithType :: (HasNodeError err, HasDBid NodeType) => NodeType -> Cmd err [NodeId]
222 223 224 225
getNodesIdWithType nt = do
  ns <- runOpaQuery $ selectNodesIdWithType nt
  pure (map NodeId ns)

226
selectNodesIdWithType :: HasDBid NodeType
227
                      => NodeType -> Select (Column SqlInt4)
228
selectNodesIdWithType nt = proc () -> do
229
    row@(Node _ _ tn _ _ _ _ _) <- queryNodeTable -< ()
230
    restrict -< tn .== (sqlInt4 $ toDBid nt)
231
    returnA -< _node_id row
232

233
------------------------------------------------------------------------
234

235
nodeExists :: (HasNodeError err) => NodeId -> Cmd err Bool
236 237
nodeExists nId = (== [PGS.Only True])
  <$> runPGSQuery [sql|SELECT true FROM nodes WHERE id = ? |] (PGS.Only nId)
238

239 240 241 242 243 244
getNode :: HasNodeError err => NodeId -> Cmd err (Node Value)
getNode nId = do
  maybeNode <- headMay <$> runOpaQuery (selectNode (pgNodeId nId))
  case maybeNode of
    Nothing -> nodeError (DoesNotExist nId)
    Just  r -> pure r
245

246 247
getNodeWith :: (HasNodeError err, JSONB a)
            => NodeId -> proxy a -> Cmd err (Node a)
248
getNodeWith nId _ = do
249 250 251 252
  maybeNode <- headMay <$> runOpaQuery (selectNode (pgNodeId nId))
  case maybeNode of
    Nothing -> nodeError (DoesNotExist nId)
    Just  r -> pure r
253

254

255
------------------------------------------------------------------------
256
-- | Sugar to insert Node with NodeType in Database
257 258
insertDefaultNode :: HasDBid NodeType
                  => NodeType -> ParentId -> UserId -> Cmd err [NodeId]
259
insertDefaultNode nt p u = insertNode nt Nothing Nothing p u
260

261 262 263 264 265 266 267 268
insertDefaultNodeIfNotExists :: HasDBid NodeType
                             => NodeType -> ParentId -> UserId -> Cmd err [NodeId]
insertDefaultNodeIfNotExists nt p u = do
  children <- getChildrenByType p nt
  case children of
    [] -> insertDefaultNode nt p u
    xs -> pure xs

269 270
insertNode :: HasDBid NodeType
           => NodeType -> Maybe Name -> Maybe DefaultHyperdata -> ParentId -> UserId -> Cmd err [NodeId]
271
insertNode nt n h p u = insertNodesR [nodeW nt n h p u]
272

273 274
nodeW ::  HasDBid NodeType
       => NodeType -> Maybe Name -> Maybe DefaultHyperdata -> ParentId -> UserId -> NodeWrite
275
nodeW nt n h p u = node nt n' h' (Just p) u
276
  where
277 278
    n' = fromMaybe (defaultName nt) n
    h' = maybe     (defaultHyperdata nt) identity h
279

280
------------------------------------------------------------------------
281
node :: (ToJSON a, Hyperdata a, HasDBid NodeType)
282 283 284 285 286 287
     => NodeType
     -> Name
     -> a
     -> Maybe ParentId
     -> UserId
     -> NodeWrite
288
node nodeType name hyperData parentId userId =
289
  Node Nothing Nothing
290 291
       (sqlInt4 typeId)
       (sqlInt4 userId)
292
       (pgNodeId <$> parentId)
293
       (sqlStrictText name)
294
       Nothing
295
       (sqlJSONB $ cs $ encode hyperData)
296
    where
297
      typeId = toDBid nodeType
298 299 300 301 302

                  -------------------------------
insertNodes :: [NodeWrite] -> Cmd err Int64
insertNodes ns = mkCmd $ \conn -> runInsert_ conn $ Insert nodeTable ns rCount Nothing

Alexandre Delanoë's avatar
Alexandre Delanoë committed
303 304
{-
insertNodes' :: [Node a] -> Cmd err Int64
305 306 307 308 309 310
insertNodes' ns = mkCmd $ \conn -> runInsert_ conn
                        $ Insert nodeTable ns' rCount Nothing
  where
    ns' :: [NodeWrite]
    ns' = map (\(Node i t u p n d h)
                -> Node (pgNodeId          <$> i)
311 312
                        (sqlInt4 $ toDBid      t)
                        (sqlInt4                u)
313
                        (pgNodeId          <$> p)
314
                        (sqlStrictText          n)
315 316 317
                        (pgUTCTime         <$> d)
                        (pgJSONB $ cs $ encode h)
              ) ns
Alexandre Delanoë's avatar
Alexandre Delanoë committed
318
-}
319

320 321
insertNodesR :: [NodeWrite] -> Cmd err [NodeId]
insertNodesR ns = mkCmd $ \conn ->
322
  runInsert_ conn (Insert nodeTable ns (rReturning (\(Node i _ _ _ _ _ _ _) -> i)) Nothing)
323 324

insertNodesWithParent :: Maybe ParentId -> [NodeWrite] -> Cmd err Int64
325
insertNodesWithParent pid ns = insertNodes (set node_parent_id (pgNodeId <$> pid) <$> ns)
326 327

insertNodesWithParentR :: Maybe ParentId -> [NodeWrite] -> Cmd err [NodeId]
328
insertNodesWithParentR pid ns = insertNodesR (set node_parent_id (pgNodeId <$> pid) <$> ns)
329 330 331 332
------------------------------------------------------------------------
-- TODO
-- currently this function removes the child relation
-- needs a Temporary type between Node' and NodeWriteT
333

334 335
node2table :: HasDBid NodeType
           => UserId -> Maybe ParentId -> Node' -> NodeWrite
336
node2table uid pid (Node' nt txt v []) = Node Nothing Nothing (sqlInt4 $ toDBid nt) (sqlInt4 uid) (fmap pgNodeId pid) (sqlStrictText txt) Nothing (sqlStrictJSONB $ cs $ encode v)
337 338 339 340 341 342 343 344 345 346
node2table _ _ (Node' _ _ _ _) = panic "node2table: should not happen, Tree insert not implemented yet"


data Node' = Node' { _n_type :: NodeType
                   , _n_name :: Text
                   , _n_data :: Value
                   , _n_children :: [Node']
                   } deriving (Show)

mkNodes :: [NodeWrite] -> Cmd err Int64
347 348
mkNodes ns = mkCmd $ \conn -> runInsert_ conn
                   $ Insert nodeTable ns rCount Nothing
349 350 351 352 353

mkNodeR :: [NodeWrite] -> Cmd err [NodeId]
mkNodeR ns = mkCmd $ \conn -> runInsert_ conn $ Insert nodeTable ns (rReturning _node_id) Nothing

------------------------------------------------------------------------
354 355
childWith ::  HasDBid NodeType
           => UserId -> ParentId -> Node' -> NodeWrite
356 357 358 359 360 361 362 363 364 365 366 367 368
childWith uId pId (Node' NodeDocument txt v []) = node2table uId (Just pId) (Node' NodeDocument txt v [])
childWith uId pId (Node' NodeContact  txt v []) = node2table uId (Just pId) (Node' NodeContact txt v [])
childWith _   _   (Node' _        _   _ _) = panic "This NodeType can not be a child"


-- =================================================================== --
-- |
-- CorpusDocument is a corpus made from a set of documents
-- CorpusContact  is a corpus made from a set of contacts (syn of Annuaire)
data CorpusType = CorpusDocument | CorpusContact

class MkCorpus a
  where
369
    mk :: HasDBid NodeType => Maybe Name -> Maybe a -> ParentId -> UserId -> Cmd err [NodeId]
370 371 372

instance MkCorpus HyperdataCorpus
  where
373 374
    mk n Nothing  p u = insertNode NodeCorpus n Nothing p u
    mk n (Just h) p u = insertNode NodeCorpus n (Just $ DefaultCorpus h) p u
375 376 377 378


instance MkCorpus HyperdataAnnuaire
  where
379 380
    mk n Nothing  p u = insertNode NodeCorpus   n Nothing p u
    mk n (Just h) p u = insertNode NodeAnnuaire n (Just $ DefaultAnnuaire h) p u
381 382


383
getOrMkList :: (HasNodeError err, HasDBid NodeType)
384 385 386
            => ParentId
            -> UserId
            -> Cmd err ListId
387 388 389
getOrMkList pId uId =
  maybe (mkList' pId uId) (pure . view node_id) . headMay =<< getListsWithParentId pId
    where
390
      mkList' pId' uId' = maybe (nodeError MkNode) pure . headMay =<< insertDefaultNode NodeList pId' uId'
391

392
-- | TODO remove defaultList
393
defaultList :: (HasNodeError err, HasDBid NodeType) => CorpusId -> Cmd err ListId
394 395 396
defaultList cId =
  maybe (nodeError NoListFound) (pure . view node_id) . headMay =<< getListsWithParentId cId

397 398 399
defaultListMaybe :: (HasNodeError err, HasDBid NodeType) => CorpusId -> Cmd err (Maybe NodeId)
defaultListMaybe cId = headMay <$> map (view node_id ) <$> getListsWithParentId cId

400
getListsWithParentId :: HasDBid NodeType => NodeId -> Cmd err [Node HyperdataList]
401
getListsWithParentId n = runOpaQuery $ selectNodesWith' n (Just NodeList)