2 Module : Gargantext.Database.Node.Document.Insert
3 Description : Importing context of texts (documents)
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
10 * Purpose of this module
12 Enabling "common goods" of text data and respecting privacy.
14 Gargantext shares as "common good" the links between context of texts
15 and terms / words / ngrams.
17 Basically a context of text can be defined as a document (see 'Gargantext.Text').
19 Issue to tackle in that module: each global document of Gargantext has
20 to be unique, then shared, but how to respect privacy if needed ?
23 * Methodology to get uniqueness and privacy by design
25 As a consequence, when importing/inserting a new document in Gargantext,
26 a policy for the uniqueness of the inserted docuemnts has to be defined.
28 That is the purpose of this module which defines its main concepts.
30 Unique identifier in database is of a 3-tuple of 3 policies that
31 together define uniqueness:
33 - Design policy: type of node is needed as TypenameId, that is a
34 Document or Individual or something else;
36 - Privacy policy: with ParentId, parent becomes unique, then it enables
37 users to get their own copy without sharing it with all the users of the
38 database (in others words parent_id is necessary to preserve privacy for
41 - Hash policy: this UniqId is a sha256 uniq id which is the result of
42 the concatenation of the parameters defined by @hashParameters@.
45 > insertTest :: FromRow r => CorpusId -> [Node HyperdataDocument] -> IO [r]
46 > insertTest :: IO [ReturnId]
47 > insertTest = connectGargandb "gargantext.ini"
48 > >>= \conn -> insertDocuments conn 1 452162 hyperdataDocuments
51 ------------------------------------------------------------------------
52 {-# LANGUAGE DeriveDataTypeable #-}
53 {-# LANGUAGE DeriveGeneric #-}
54 {-# LANGUAGE FlexibleInstances #-}
55 {-# LANGUAGE NoImplicitPrelude #-}
56 {-# LANGUAGE OverloadedStrings #-}
57 {-# LANGUAGE QuasiQuotes #-}
58 {-# LANGUAGE TypeSynonymInstances #-}
59 ------------------------------------------------------------------------
60 module Gargantext.Database.Node.Document.Insert where
62 import Control.Lens (set, view)
63 import Control.Lens.Prism
64 import Control.Lens.Cons
65 import Data.Aeson (toJSON, Value)
66 import Data.Maybe (maybe)
67 import Data.Text (Text)
68 import Data.Typeable (Typeable)
69 import Database.PostgreSQL.Simple (FromRow, Query, query, Only(..))
70 import Database.PostgreSQL.Simple.FromRow (fromRow, field)
71 import Database.PostgreSQL.Simple.SqlQQ
72 import Database.PostgreSQL.Simple.ToField (toField)
73 import Database.PostgreSQL.Simple.ToRow (ToRow(..))
74 import Database.PostgreSQL.Simple.Types (Values(..), QualifiedIdentifier(..))
75 import GHC.Generics (Generic)
76 import Gargantext.Database.Config (nodeTypeId)
77 import Gargantext.Database.Node (mkCmd, Cmd(..))
78 import Gargantext.Database.Node.Contact -- (HyperdataContact(..), ContactWho(..))
79 import Gargantext.Database.Types.Node
80 import Gargantext.Prelude
81 import qualified Data.ByteString.Lazy.Char8 as DC (pack)
82 import qualified Data.Digest.Pure.SHA as SHA (sha256, showDigest)
83 import qualified Data.Text as DT (pack, unpack, concat, take)
85 -- TODO : the import of Document constructor below does not work
86 -- import Gargantext.Database.Types.Node (Document)
87 --import Gargantext.Database.Types.Node (docExample, hyperdataDocument, HyperdataDocument(..)
88 -- , hyperdataDocument_uniqId
89 -- , hyperdataDocument_title
90 -- , hyperdataDocument_abstract
91 -- , hyperdataDocument_source
92 -- , Node(..), node_typename
94 -- , node_parentId, node_name, node_hyperdata, hyperdataDocuments
97 {-| To Print result query
98 import Data.ByteString.Internal (ByteString)
99 import Database.PostgreSQL.Simple (formatQuery)
102 ---------------------------------------------------------------------------
103 -- * Main Insert functions
105 -- ** Database configuration
106 -- Administrator of the database has to create a uniq index as following SQL command:
107 -- `create unique index on nodes (typename, parent_id, (hyperdata ->> 'uniqId'));`
109 -- | Insert Document main function
110 -- UserId : user who is inserting the documents
111 -- ParentId : folder ID which is parent of the inserted documents
114 data ToDbData = ToDbDocument HyperdataDocument | ToDbContact HyperdataContact
116 insertDocuments :: UserId -> ParentId -> NodeType -> [ToDbData] -> Cmd [ReturnId]
117 insertDocuments uId pId nodeType hs = mkCmd $ \c -> query c queryInsert (Only $ Values fields $ prepare uId pId nodeType hs)
119 fields = map (\t-> QualifiedIdentifier Nothing t) inputSqlTypes
121 -- | Debug SQL function
123 -- to print rendered query (Debug purpose) use @formatQuery@ function.
125 insertDocuments_Debug :: (Hyperdata a, ToJSON a, ToRow a) => UserId -> ParentId -> [a] -> Cmd ByteString
126 insertDocuments_Debug uId pId hs = mkCmd $ \conn -> formatQuery conn queryInsert (Only $ Values fields inputData)
128 fields = map (\t-> QualifiedIdentifier Nothing t) inputSqlTypes
129 inputData = prepare uId pId hs
133 -- | Input Tables: types of the tables
134 inputSqlTypes :: [Text]
135 inputSqlTypes = map DT.pack ["int4","int4","int4","text","jsonb"]
137 -- | SQL query to insert documents inside the database
140 WITH input_rows(typename,user_id,parent_id,name,hyperdata) AS (?)
142 INSERT INTO nodes (typename,user_id,parent_id,name,hyperdata)
143 SELECT * FROM input_rows
144 ON CONFLICT ((hyperdata ->> 'uniqIdBdd')) DO NOTHING -- on unique index
145 -- ON CONFLICT (typename, parent_id, (hyperdata ->> 'uniqId')) DO NOTHING -- on unique index
146 RETURNING id,hyperdata
149 SELECT true AS source -- true for 'newly inserted'
151 , hyperdata ->> 'uniqId' as doi
154 SELECT false AS source -- false for 'not inserted'
156 , hyperdata ->> 'uniqId' as doi
158 JOIN nodes c USING (hyperdata); -- columns of unique index
161 prepare :: UserId -> ParentId -> NodeType -> [ToDbData] -> [InputData]
162 prepare uId pId nodeType = map (\h -> InputData tId uId pId (name h) (toJSON' h))
164 tId = nodeTypeId nodeType
166 toJSON' (ToDbDocument hd) = toJSON hd
167 toJSON' (ToDbContact hc) = toJSON hc
169 name h = DT.take 255 <$> maybe "No Title" identity $ f h
171 f (ToDbDocument hd) = _hyperdataDocument_title hd
172 f (ToDbContact _ ) = Just "Contact" -- TODO view FirstName . LastName
174 ------------------------------------------------------------------------
179 -- | When documents are inserted
180 -- ReturnType after insertion
181 data ReturnId = ReturnId { reInserted :: Bool -- ^ if the document is inserted (True: is new, False: is not new)
182 , reId :: Int -- ^ always return the id of the document (even new or not new)
183 -- this is the uniq id in the database
184 , reUniqId :: Text -- ^ Hash Id with concatenation of hash parameters
185 } deriving (Show, Generic)
187 instance FromRow ReturnId where
188 fromRow = ReturnId <$> field <*> field <*> field
195 data InputData = InputData { inTypenameId :: NodeTypeId
197 , inParentId :: ParentId
200 } deriving (Show, Generic, Typeable)
202 instance ToRow InputData where
203 toRow inputData = [ toField (inTypenameId inputData)
204 , toField (inUserId inputData)
205 , toField (inParentId inputData)
206 , toField (inName inputData)
207 , toField (inHyper inputData)
210 ---------------------------------------------------------------------------
211 -- * Uniqueness of document definition
213 addUniqIdsDoc :: HyperdataDocument -> HyperdataDocument
214 addUniqIdsDoc doc = set hyperdataDocument_uniqIdBdd (Just hashBdd)
215 $ set hyperdataDocument_uniqId (Just hash) doc
217 hash = uniqId $ DT.concat $ map ($ doc) hashParametersDoc
218 hashBdd = uniqId $ DT.concat $ map ($ doc) ([(\d -> maybe' (_hyperdataDocument_bdd d))] <> hashParametersDoc)
220 uniqId :: Text -> Text
221 uniqId = DT.pack . SHA.showDigest . SHA.sha256 . DC.pack . DT.unpack
224 hashParametersDoc :: [(HyperdataDocument -> Text)]
225 hashParametersDoc = [ \d -> maybe' (_hyperdataDocument_title d)
226 , \d -> maybe' (_hyperdataDocument_abstract d)
227 , \d -> maybe' (_hyperdataDocument_source d)
228 , \d -> maybe' (_hyperdataDocument_publication_date d)
230 ---------------------------------------------------------------------------
231 -- * Uniqueness of document definition
232 -- TODO factorize with above (use the function below for tests)
233 addUniqIdsContact :: HyperdataContact -> HyperdataContact
234 addUniqIdsContact hc = set (hc_uniqIdBdd) (Just hashBdd)
235 $ set (hc_uniqId) (Just hash) hc
237 hash = uniqId $ DT.concat $ map ($ hc) hashParametersContact
238 hashBdd = uniqId $ DT.concat $ map ($ hc) ([\d -> maybe' (view hc_bdd d)] <> hashParametersContact)
240 uniqId :: Text -> Text
241 uniqId = DT.pack . SHA.showDigest . SHA.sha256 . DC.pack . DT.unpack
243 -- | TODO add more hashparameters
244 hashParametersContact :: [(HyperdataContact -> Text)]
245 hashParametersContact = [ \d -> maybe' $ view (hc_who . _Just . cw_firstName) d
246 , \d -> maybe' $ view (hc_who . _Just . cw_lastName ) d
247 , \d -> maybe' $ view (hc_where . _Just . _head . cw_touch . _Just . ct_mail) d
252 maybe' :: Maybe Text -> Text
253 maybe' = maybe (DT.pack "") identity
255 ---------------------------------------------------------------------------