2 Module : Gargantext.Database.Query.Facet
3 Description : Main requests of Node to the database
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
11 {-# OPTIONS_GHC -fno-warn-orphans #-}
12 {-# OPTIONS_GHC -fno-warn-name-shadowing #-}
14 {-# LANGUAGE Arrows #-}
15 {-# LANGUAGE FunctionalDependencies #-}
16 {-# LANGUAGE QuasiQuotes #-}
17 {-# LANGUAGE NoMonomorphismRestriction #-}
18 {-# LANGUAGE TemplateHaskell #-}
19 {-# LANGUAGE TypeFamilies #-}
20 ------------------------------------------------------------------------
21 module Gargantext.Database.Query.Facet
34 , FacetPairedReadNullAgg
39 import Control.Arrow (returnA)
40 import Control.Lens ((^.))
41 import Data.Aeson (FromJSON, ToJSON)
42 import Data.Aeson.TH (deriveJSON)
43 import Data.Profunctor.Product.TH (makeAdaptorAndInstance)
45 import qualified Data.Text as T
46 import Data.Time (UTCTime)
47 import Data.Time.Segment (jour)
49 import Protolude hiding (null, map, sum, not)
51 import Test.QuickCheck (elements)
52 import Test.QuickCheck.Arbitrary
53 import qualified Opaleye.Internal.Unpackspec()
55 import Gargantext.Core.Types
56 import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixSwagger, wellNamedSchema)
57 import Gargantext.Database.Admin.Config (nodeTypeId)
58 import Gargantext.Database.Admin.Types.Hyperdata
59 import Gargantext.Database.Query.Filter
60 import Gargantext.Database.Query.Join (leftJoin5)
61 import Gargantext.Database.Query.Table.Ngrams
62 import Gargantext.Database.Query.Table.NodeNode
63 import Gargantext.Database.Query.Table.NodeNodeNgrams
64 import Gargantext.Database.Prelude
65 import Gargantext.Database.Schema.Node
67 ------------------------------------------------------------------------
70 -- data Facet = FacetDoc | FacetSources | FacetAuthors | FacetTerms
71 -- deriving (Show, Generic)
72 --instance FromJSON Facet
73 --instance ToJSON Facet
79 type FacetDoc = Facet NodeId UTCTime Title HyperdataDocument (Maybe Category) (Maybe Double) (Maybe Double)
80 -- type FacetSources = FacetDoc
81 -- type FacetAuthors = FacetDoc
82 -- type FacetTerms = FacetDoc
85 data Facet id created title hyperdata category ngramCount score =
86 FacetDoc { facetDoc_id :: id
87 , facetDoc_created :: created
88 , facetDoc_title :: title
89 , facetDoc_hyperdata :: hyperdata
90 , facetDoc_category :: category
91 , facetDoc_ngramCount :: ngramCount
92 , facetDoc_score :: score
93 } deriving (Show, Generic)
95 data Facet id date hyperdata score =
96 FacetDoc { facetDoc_id :: id
97 , facetDoc_date :: date
98 , facetDoc_hyperdata :: hyperdata
99 , facetDoc_score :: score
100 } deriving (Show, Generic)
103 data Pair i l = Pair {
106 } deriving (Show, Generic)
107 $(deriveJSON (unPrefix "_p_") ''Pair)
108 $(makeAdaptorAndInstance "pPair" ''Pair)
110 instance (Typeable i, Typeable l, ToSchema i, ToSchema l) => ToSchema (Pair i l) where
111 declareNamedSchema = wellNamedSchema "_p_"
112 instance (Arbitrary i, Arbitrary l) => Arbitrary (Pair i l) where
113 arbitrary = Pair <$> arbitrary <*> arbitrary
115 data FacetPaired id date hyperdata score =
116 FacetPaired {_fp_id :: id
118 ,_fp_hyperdata :: hyperdata
120 } deriving (Show, Generic)
121 $(deriveJSON (unPrefix "_fp_") ''FacetPaired)
122 $(makeAdaptorAndInstance "pFacetPaired" ''FacetPaired)
126 instance ( ToSchema id
134 ) => ToSchema (FacetPaired id date hyperdata score) where
135 declareNamedSchema = wellNamedSchema "_fp_"
137 instance ( Arbitrary id
139 , Arbitrary hyperdata
141 ) => Arbitrary (FacetPaired id date hyperdata score) where
142 arbitrary = FacetPaired <$> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary
144 type FacetPairedRead = FacetPaired (Column PGInt4 )
145 (Column PGTimestamptz)
149 type FacetPairedReadNull = FacetPaired (Column (Nullable PGInt4) )
150 (Column (Nullable PGTimestamptz))
151 (Column (Nullable PGJsonb) )
152 (Column (Nullable PGInt4) )
154 type FacetPairedReadNullAgg = FacetPaired (Aggregator (Column (Nullable PGInt4) )
155 (Column (Nullable PGInt4) )
157 (Aggregator (Column (Nullable PGTimestamptz))
158 (Column (Nullable PGTimestamptz))
161 (Aggregator (Column (Nullable PGJsonb) )
162 (Column (Nullable PGJsonb) )
164 (Aggregator (Column (Nullable PGInt4) )
165 (Column (Nullable PGInt4) )
172 $(deriveJSON (unPrefix "facetDoc_") ''Facet)
174 -- | Documentation instance
175 instance ToSchema FacetDoc where
176 declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "facetDoc_")
178 -- | Mock and Quickcheck instances
179 instance Arbitrary FacetDoc where
180 arbitrary = elements [ FacetDoc id' (jour year 01 01) t hp (Just cat) (Just ngramCount) (Just score)
182 , year <- [1990..2000]
183 , t <- ["title", "another title"]
184 , hp <- arbitraryHyperdataDocuments
186 , ngramCount <- [3..100]
190 -- Facets / Views for the Front End
191 -- | Database instances
192 $(makeAdaptorAndInstance "pFacetDoc" ''Facet)
193 -- $(makeLensesWith abbreviatedFields ''Facet)
195 type FacetDocRead = Facet (Column PGInt4 )
196 (Column PGTimestamptz)
199 (Column (Nullable PGInt4)) -- Category
200 (Column (Nullable PGFloat8)) -- Ngrams Count
201 (Column (Nullable PGFloat8)) -- Score
203 -----------------------------------------------------------------------
204 -----------------------------------------------------------------------
205 data OrderBy = DateAsc | DateDesc
206 | TitleAsc | TitleDesc
207 | ScoreDesc | ScoreAsc
208 | SourceAsc | SourceDesc
209 deriving (Generic, Enum, Bounded, Read, Show)
211 instance FromHttpApiData OrderBy
213 parseUrlPiece "DateAsc" = pure DateAsc
214 parseUrlPiece "DateDesc" = pure DateDesc
215 parseUrlPiece "TitleAsc" = pure TitleAsc
216 parseUrlPiece "TitleDesc" = pure TitleDesc
217 parseUrlPiece "ScoreAsc" = pure ScoreAsc
218 parseUrlPiece "ScoreDesc" = pure ScoreDesc
219 parseUrlPiece "SourceAsc" = pure SourceAsc
220 parseUrlPiece "SourceDesc" = pure SourceDesc
221 parseUrlPiece _ = Left "Unexpected value of OrderBy"
223 instance ToParamSchema OrderBy
224 instance FromJSON OrderBy
225 instance ToJSON OrderBy
226 instance ToSchema OrderBy
227 instance Arbitrary OrderBy
229 arbitrary = elements [minBound..maxBound]
232 -- TODO-SECURITY check
235 runViewAuthorsDoc :: ContactId -> IsTrash -> Maybe Offset -> Maybe Limit -> Maybe OrderBy -> Cmd err [FacetDoc]
236 runViewAuthorsDoc cId t o l order = runOpaQuery $ filterWith o l order $ viewAuthorsDoc cId t ntId
241 viewAuthorsDoc :: ContactId -> IsTrash -> NodeType -> Query FacetDocRead
242 viewAuthorsDoc cId _ nt = proc () -> do
243 (doc,(_,(_,(_,contact)))) <- queryAuthorsDoc -< ()
245 {-nn <- queryNodeNodeTable -< ()
246 restrict -< nn_node1_id nn .== _node_id doc
247 -- restrict -< nn_delete nn .== (pgBool t)
250 restrict -< _node_id contact .== (toNullable $ pgNodeId cId)
251 restrict -< _node_typename doc .== (pgInt4 $ nodeTypeId nt)
253 returnA -< FacetDoc (_node_id doc)
256 (_node_hyperdata doc)
257 (toNullable $ pgInt4 1)
258 (toNullable $ pgDouble 1)
259 (toNullable $ pgDouble 1)
261 queryAuthorsDoc :: Query (NodeRead, (NodeNodeNgramsReadNull, (NgramsReadNull, (NodeNodeNgramsReadNull, NodeReadNull))))
262 queryAuthorsDoc = leftJoin5 queryNodeTable queryNodeNodeNgramsTable queryNgramsTable queryNodeNodeNgramsTable queryNodeTable cond12 cond23 cond34 cond45
264 cond12 :: (NodeNodeNgramsRead, NodeRead) -> Column PGBool
265 cond12 (nodeNgram, doc) = _node_id doc
266 .== _nnng_node1_id nodeNgram
268 cond23 :: (NgramsRead, (NodeNodeNgramsRead, NodeReadNull)) -> Column PGBool
269 cond23 (ngrams, (nodeNgram, _)) = ngrams^.ngrams_id
270 .== _nnng_ngrams_id nodeNgram
272 cond34 :: (NodeNodeNgramsRead, (NgramsRead, (NodeNodeNgramsReadNull, NodeReadNull))) -> Column PGBool
273 cond34 (nodeNgram2, (ngrams, (_,_)))= ngrams^.ngrams_id .== _nnng_ngrams_id nodeNgram2
275 cond45 :: (NodeRead, (NodeNodeNgramsRead, (NgramsReadNull, (NodeNodeNgramsReadNull, NodeReadNull)))) -> Column PGBool
276 cond45 (contact, (nodeNgram2, (_, (_,_)))) = _node_id contact .== _nnng_node1_id nodeNgram2
279 ------------------------------------------------------------------------
281 -- TODO-SECURITY check
282 runViewDocuments :: CorpusId
288 -> Cmd err [FacetDoc]
289 runViewDocuments cId t o l order query = do
290 runOpaQuery $ filterWith o l order sqlQuery
292 ntId = nodeTypeId NodeDocument
293 sqlQuery = viewDocuments cId t ntId query
295 runCountDocuments :: CorpusId -> IsTrash -> Maybe Text -> Cmd err Int
296 runCountDocuments cId t mQuery = do
297 runCountOpaQuery sqlQuery
299 sqlQuery = viewDocuments cId t (nodeTypeId NodeDocument) mQuery
302 viewDocuments :: CorpusId
306 -> Query FacetDocRead
307 viewDocuments cId t ntId mQuery = proc () -> do
308 n <- queryNodeTable -< ()
309 nn <- queryNodeNodeTable -< ()
310 restrict -< n^.node_id .== nn^.nn_node2_id
311 restrict -< nn^.nn_node1_id .== (pgNodeId cId)
312 restrict -< n^.node_typename .== (pgInt4 ntId)
313 restrict -< if t then nn^.nn_category .== (pgInt4 0)
314 else nn^.nn_category .>= (pgInt4 1)
316 let query = (fromMaybe "" mQuery)
317 iLikeQuery = T.intercalate "" ["%", query, "%"]
318 restrict -< (n^.node_name) `ilike` (pgStrictText iLikeQuery)
320 returnA -< FacetDoc (_node_id n)
324 (toNullable $ nn^.nn_category)
325 (toNullable $ nn^.nn_score)
326 (toNullable $ nn^.nn_score)
328 ------------------------------------------------------------------------
329 filterWith :: (PGOrd date, PGOrd title, PGOrd category, PGOrd score, hyperdata ~ Column SqlJsonb) =>
330 Maybe Gargantext.Core.Types.Offset
331 -> Maybe Gargantext.Core.Types.Limit
333 -> Select (Facet id (Column date) (Column title) hyperdata (Column category) ngramCount (Column score))
334 -> Select (Facet id (Column date) (Column title) hyperdata (Column category) ngramCount (Column score))
335 filterWith o l order q = limit' l $ offset' o $ orderBy (orderWith order) q
338 orderWith :: (PGOrd b1, PGOrd b2, PGOrd b3)
340 -> Order (Facet id (Column b1) (Column b2) (Column SqlJsonb) (Column b3) ngramCount score)
341 orderWith (Just DateAsc) = asc facetDoc_created
342 orderWith (Just DateDesc) = desc facetDoc_created
344 orderWith (Just TitleAsc) = asc facetDoc_title
345 orderWith (Just TitleDesc) = desc facetDoc_title
347 orderWith (Just ScoreAsc) = asc facetDoc_category
348 orderWith (Just ScoreDesc) = desc facetDoc_category
350 orderWith (Just SourceAsc) = asc facetDoc_source
351 orderWith (Just SourceDesc) = desc facetDoc_source
353 orderWith _ = asc facetDoc_created
355 facetDoc_source :: PGIsJson a
356 => Facet id created title (Column a) favorite ngramCount score
357 -> Column (Nullable PGText)
358 facetDoc_source x = toNullable (facetDoc_hyperdata x) .->> pgString "source"