]> Git — Sourcephile - gargantext.git/blob - bin/gargantext-upgrade/Main.hs
[db] fixes for context_node_ngrams_view materialized view
[gargantext.git] / bin / gargantext-upgrade / Main.hs
1 {-|
2 Module : Main.hs
3 Description : Gargantext Import Corpus
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
8 Portability : POSIX
9
10 Import a corpus binary.
11
12 -}
13
14 {-# LANGUAGE Strict #-}
15 {-# LANGUAGE QuasiQuotes #-}
16
17 module Main where
18
19 import Data.Either (Either(..))
20 import Database.PostgreSQL.Simple.SqlQQ (sql)
21 import GHC.IO.Exception (IOException)
22 import Gargantext.API.Admin.EnvTypes (DevEnv)
23 import Gargantext.API.Dev (withDevEnv, runCmdDev)
24 import Gargantext.API.Ngrams.Tools (migrateFromDirToDb)
25 import Gargantext.API.Node () -- instances only
26 import Gargantext.API.Prelude (GargError)
27 import Gargantext.Core (HasDBid(toDBid))
28 import Gargantext.Core.Types.Individu (User(..))
29 import Gargantext.Database.Action.Flow (getOrMk_RootWithCorpus)
30 import Gargantext.Database.Admin.Config (userMaster, corpusMasterName)
31 import Gargantext.Database.Admin.Trigger.Init
32 import Gargantext.Database.Admin.Types.Hyperdata (HyperdataCorpus)
33 import Gargantext.Database.Admin.Types.Node (NodeType(NodeDocument, NodeContact))
34 import Gargantext.Database.Prelude (Cmd'', Cmd, execPGSQuery)
35 import Gargantext.Prelude
36 import Gargantext.Prelude.Config (GargConfig(..), readConfig)
37 import Prelude (getLine)
38 import System.Environment (getArgs)
39 import qualified Data.List as List (cycle, concat, take, unlines)
40
41 main :: IO ()
42 main = do
43
44 let ___ = putStrLn
45 $ List.concat
46 $ List.take 72
47 $ List.cycle ["_"]
48
49 ___
50 putStrLn "GarganText upgrade to version 0.0.6.9.9.4.4"
51 ___
52
53 params@[iniPath] <- getArgs
54 _ <- if length params /= 1
55 then panic "Usage: ./gargantext-upgrade gargantext.ini"
56 else pure ()
57
58 putStrLn $ List.unlines
59 [ "Your Database defined in gargantext.ini will be upgraded."
60 , "We stronlgy recommend you to make a backup using pg_dump."
61 , ""
62 , "Press ENTER if you want to continue, CTRL+C if you want to stop."
63 ]
64
65 _ok <- getLine
66
67 cfg <- readConfig iniPath
68 let _secret = _gc_secretkey cfg
69
70 withDevEnv iniPath $ \env -> do
71 _ <- runCmdDev env addIndex
72 _ <- runCmdDev env refreshIndex
73
74
75 ___
76 putStrLn "Uprade done with success !"
77 ___
78 pure ()
79
80 refreshIndex :: Cmd'' DevEnv IOException ()
81 refreshIndex = do
82 _ <- execPGSQuery [sql| REFRESH MATERIALIZED VIEW CONCURRENTLY context_node_ngrams_view; |] ()
83 pure ()
84
85 addIndex :: Cmd'' DevEnv IOException Int64
86 addIndex = do
87 execPGSQuery query ()
88 where
89 query = [sql|
90 CREATE MATERIALIZED VIEW IF NOT EXISTS context_node_ngrams_view AS
91 SELECT DISTINCT context_node_ngrams.context_id, ngrams_id, nodes_contexts.node_id
92 FROM nodes_contexts
93 JOIN context_node_ngrams
94 ON context_node_ngrams.context_id = nodes_contexts.context_id;
95
96 CREATE INDEX IF NOT EXISTS context_node_ngrams_context_id_ngrams_id_idx
97 ON context_node_ngrams(context_id, ngrams_id);
98
99 CREATE INDEX IF NOT EXISTS context_node_ngrams_view_context_id_idx
100 ON context_node_ngrams_view(context_id);
101 CREATE INDEX IF NOT EXISTS context_node_ngrams_view_ngrams_id_idx
102 ON context_node_ngrams_view(ngrams_id);
103 CREATE INDEX IF NOT EXISTS context_node_ngrams_view_node_id_idx
104 ON context_node_ngrams_view(node_id);
105 CREATE UNIQUE INDEX IF NOT EXISTS context_node_ngrams_view_context_ngrams_node_uniq_idx
106 ON context_node_ngrams_view (context_id, ngrams_id, node_id);
107
108 CREATE INDEX IF NOT EXISTS node_stories_ngrams_id_idx
109 ON node_stories(ngrams_id);
110 |]