2 Module : Gargantext.Database.Schema.NodesNgramsRepo
3 Description : NodeNgram for Ngram indexation or Lists
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
13 {-# OPTIONS_GHC -fno-warn-orphans #-}
15 {-# LANGUAGE Arrows #-}
16 {-# LANGUAGE FlexibleContexts #-}
17 {-# LANGUAGE FlexibleInstances #-}
18 {-# LANGUAGE FunctionalDependencies #-}
19 {-# LANGUAGE GeneralizedNewtypeDeriving #-}
20 {-# LANGUAGE MultiParamTypeClasses #-}
21 {-# LANGUAGE NoImplicitPrelude #-}
22 {-# LANGUAGE OverloadedStrings #-}
23 {-# LANGUAGE QuasiQuotes #-}
24 {-# LANGUAGE RankNTypes #-}
25 {-# LANGUAGE TemplateHaskell #-}
28 module Gargantext.Database.Schema.NodesNgramsRepo
31 import Data.Map.Strict.Patch (PatchMap)
32 import Gargantext.Database.Schema.Prelude
33 import Gargantext.API.Ngrams (NgramsStatePatch, NgramsTablePatch)
34 import Gargantext.Database.Schema.Ngrams (NgramsType)
35 import Gargantext.Database.Admin.Types.Node (NodeId)
36 import Gargantext.Database.Admin.Utils (mkCmd, Cmd, runOpaQuery)
37 import Gargantext.Prelude
40 data RepoDbPoly version patches
41 = RepoDbNgrams { _rdp_version :: !version
42 , _rdp_patches :: !patches
46 = RepoDbPoly (Column PGInt4)
49 = RepoDbPoly (Column PGInt4)
52 type RepoDbNgrams = RepoDbPoly Int NgramsStatePatch
53 $(makeAdaptorAndInstance "pRepoDbNgrams" ''RepoDbPoly)
54 makeLenses ''RepoDbPoly
56 instance QueryRunnerColumnDefault PGJsonb
58 (PatchMap NodeId NgramsTablePatch))
60 queryRunnerColumnDefault = fieldQueryRunnerColumn
63 repoTable :: Table RepoDbWrite RepoDbRead
64 repoTable = Table "nodes_ngrams_repo"
65 (pRepoDbNgrams RepoDbNgrams
66 { _rdp_version = required "version"
67 , _rdp_patches = required "patches"
72 selectRepo :: Cmd err [RepoDbNgrams]
73 selectRepo = runOpaQuery selectPatches
75 selectPatches :: Query RepoDbRead
76 selectPatches = proc () -> do
77 repos <- queryTable repoTable -< ()
81 insertRepos :: [NgramsStatePatch] -> Cmd err Int64
82 insertRepos ns = mkCmd $ \conn -> runInsert_ conn $ Insert repoTable (toWrite ns) rCount Nothing
84 toWrite :: [NgramsStatePatch] -> [RepoDbWrite]
86 --ns' = map (\(RepoDbNgrams v ps) -> RepoDbWrite (pgInt4 v) (pgJSONB ps)) ns