Commit 0ba19424 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[FEAT] SQL fun to insert postagging

parent fbc1dbea
...@@ -178,6 +178,7 @@ CREATE UNIQUE INDEX ON public.nodes USING btree (hash_id); ...@@ -178,6 +178,7 @@ CREATE UNIQUE INDEX ON public.nodes USING btree (hash_id);
CREATE UNIQUE INDEX ON public.ngrams (terms); -- TEST GIN CREATE UNIQUE INDEX ON public.ngrams (terms); -- TEST GIN
CREATE INDEX ON public.ngrams USING btree (id, terms); CREATE INDEX ON public.ngrams USING btree (id, terms);
CREATE UNIQUE INDEX ON public.ngrams_postag (lang_id,algo_id,postag,ngrams_id,lemm_id);
CREATE INDEX ON public.node_ngrams USING btree (node_id,node_subtype); CREATE INDEX ON public.node_ngrams USING btree (node_id,node_subtype);
CREATE UNIQUE INDEX ON public.node_ngrams USING btree (node_id,node_subtype, ngrams_id); CREATE UNIQUE INDEX ON public.node_ngrams USING btree (node_id,node_subtype, ngrams_id);
......
{-|
Module : Gargantext.Database.Query.Table.NgramsPostag
Description : Deal with in Gargantext Database.
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
{-# LANGUAGE Arrows #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-}
module Gargantext.Database.Query.Table.NgramsPostag
where
import Data.Text (Text)
import Gargantext.Database.Prelude (Cmd)
import Gargantext.Database.Prelude (runPGSQuery)
import Gargantext.Database.Schema.Ngrams
import Gargantext.Database.Schema.Prelude
import Gargantext.Prelude
import qualified Database.PostgreSQL.Simple as PGS
type NgramsPostagInsert = ( Int
, Int
, Text
, Text
, Int
, Text
, Int
)
insertNgramsPostag :: [NgramsPostagInsert] -> Cmd err [NgramIds]
insertNgramsPostag ns = runPGSQuery queryInsertNgramsPostag (PGS.Only $ Values fields ns)
where
fields = map (\t -> QualifiedIdentifier Nothing t) $ snd fields_name
fields_name :: ( [Text], [Text])
fields_name = ( ["lang_id", "algo_id", "postag", "form", "form_n", "lem" , "lem_n"]
, ["int4" , "int4" , "text" , "text", "int4" , "text", "int4" ]
)
----------------------
queryInsertNgramsPostag :: PGS.Query
queryInsertNgramsPostag = [sql|
WITH input_rows(lang_id,algo_id,postag,form,form_n, lem, lem_n)
AS (?)
-- ((VALUES (1::"int4",2::"int4",'VB'::"text",'dansaient'::"text",1::"int4",'danser'::"text",1::"int4")))
------------------------------------------------
, ins_form AS (INSERT INTO ngrams (terms,n)
SELECT ir1.form, ir1.form_n
FROM input_rows as ir1
UNION ALL
SELECT ir2.lem, ir2.lem_n
FROM input_rows as ir2
ON CONFLICT (terms)
DO NOTHING
RETURNING id,terms
)
------------------------------------------------
, ins_form_ret AS (
SELECT id, terms
FROM ins_form
UNION ALL
SELECT n.id, ir.form
FROM input_rows ir
JOIN ngrams n ON n.terms = ir.form
)
, ins_lem_ret AS (
SELECT id, terms
FROM ins_form
UNION ALL
SELECT n.id, ir.lem
FROM input_rows ir
JOIN ngrams n ON n.terms = ir.lem
)
------------------------------------------------
------------------------------------------------
, ins_postag AS ( INSERT INTO ngrams_postag (lang_id, algo_id, postag, ngrams_id, lemm_id,score)
SELECT ir.lang_id, ir.algo_id, ir.postag, form.id, lem.id, 1
FROM input_rows ir
JOIN ins_form_ret form ON form.terms = ir.form
JOIN ins_lem_ret lem ON lem.terms = ir.lem
ON CONFLICT (lang_id,algo_id,postag,ngrams_id,lemm_id)
DO UPDATE SET score = ngrams_postag.score + 1
)
SELECT * FROM ins_form_ret
|]
...@@ -20,29 +20,33 @@ ngrams in NgramsTerm Lists. ...@@ -20,29 +20,33 @@ ngrams in NgramsTerm Lists.
module Gargantext.Database.Schema.NgramsPostag module Gargantext.Database.Schema.NgramsPostag
where where
import Control.Lens
import Data.Text (Text) import Data.Text (Text)
import Gargantext.Prelude
import Gargantext.Database.Schema.Prelude import Gargantext.Database.Schema.Prelude
import Gargantext.Prelude
import qualified Database.PostgreSQL.Simple as PGS
data NgramsPosTagPoly id data NgramsPostagPoly id
lang_id lang_id
algo_id algo_id
postag postag
ngrams_id ngrams_id
lemm_id lemm_id
score score
= NgramsPosTagDB { _ngramsPosTag_id :: !id = NgramsPostagDB { _ngramsPostag_id :: !id
, _ngramsPosTag_lang_id :: !lang_id , _ngramsPostag_lang_id :: !lang_id
, _ngramsPosTag_algo_id :: !algo_id , _ngramsPostag_algo_id :: !algo_id
, _ngramsPosTag_postag :: !postag , _ngramsPostag_postag :: !postag
, _ngramsPosTag_ngrams_id :: !ngrams_id , _ngramsPostag_ngrams_id :: !ngrams_id
, _ngramsPosTag_lemm_id :: !lemm_id , _ngramsPostag_lemm_id :: !lemm_id
, _ngramsPosTag_score :: !score , _ngramsPostag_score :: !score
} deriving (Show) } deriving (Show)
------------------------------------------------------------------------ ------------------------------------------------------------------------
type NgramsPostagDB = NgramsPostagPoly (Maybe Int) Int Int (Maybe Text) Int Int Int
type NgramsPosTagWrite = NgramsPosTagPoly (Maybe (Column PGInt4)) type NgramsPosTagWrite = NgramsPostagPoly (Maybe (Column PGInt4))
(Column PGInt4) (Column PGInt4)
(Column PGInt4) (Column PGInt4)
(Maybe (Column PGText)) (Maybe (Column PGText))
...@@ -50,7 +54,7 @@ type NgramsPosTagWrite = NgramsPosTagPoly (Maybe (Column PGInt4)) ...@@ -50,7 +54,7 @@ type NgramsPosTagWrite = NgramsPosTagPoly (Maybe (Column PGInt4))
(Column PGInt4) (Column PGInt4)
(Maybe (Column PGInt4)) (Maybe (Column PGInt4))
type NgramsPosTagRead = NgramsPosTagPoly (Column PGInt4) type NgramsPosTagRead = NgramsPostagPoly (Column PGInt4)
(Column PGInt4) (Column PGInt4)
(Column PGInt4) (Column PGInt4)
(Column PGText) (Column PGText)
...@@ -58,12 +62,21 @@ type NgramsPosTagRead = NgramsPosTagPoly (Column PGInt4) ...@@ -58,12 +62,21 @@ type NgramsPosTagRead = NgramsPosTagPoly (Column PGInt4)
(Column PGInt4) (Column PGInt4)
(Column PGInt4) (Column PGInt4)
type NgramsPosTagReadNull = NgramsPosTagPoly (Column (Nullable PGInt4)) type NgramsPosTagReadNull = NgramsPostagPoly (Column (Nullable PGInt4))
(Column (Nullable PGInt4)) (Column (Nullable PGInt4))
(Column (Nullable PGInt4)) (Column (Nullable PGInt4))
(Column (Nullable PGText)) (Column (Nullable PGText))
(Column (Nullable PGInt4)) (Column (Nullable PGInt4))
(Column (Nullable PGInt4)) (Column (Nullable PGInt4))
(Column (Nullable PGInt4)) (Column (Nullable PGInt4))
makeLenses ''NgramsPostagPoly
type NgramsPosTagDB = NgramsPosTagPoly Int Int Int Text Int Int Int instance PGS.ToRow NgramsPostagDB where
toRow (NgramsPostagDB f0 f1 f2 f3 f4 f5 f6) = [ toField f0
, toField f1
, toField f2
, toField f3
, toField f4
, toField f5
, toField f6
]
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