2 Module : Gargantext.Database.Types.Nodes
3 Description : Main Types of Nodes in Database
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
12 {-# OPTIONS_GHC -fno-warn-orphans #-}
14 {-# LANGUAGE BangPatterns #-}
15 {-# LANGUAGE DeriveGeneric #-}
16 {-# LANGUAGE FlexibleInstances #-}
17 {-# LANGUAGE GeneralizedNewtypeDeriving #-}
18 {-# LANGUAGE NoImplicitPrelude #-}
19 {-# LANGUAGE OverloadedStrings #-}
20 {-# LANGUAGE TemplateHaskell #-}
21 {-# LANGUAGE GeneralizedNewtypeDeriving #-}
23 -- {-# LANGUAGE DuplicateRecordFields #-}
25 module Gargantext.Database.Types.Node
28 import Prelude (Enum, Bounded, minBound, maxBound)
30 import GHC.Generics (Generic)
32 import Control.Lens hiding (elements, (&))
33 import Control.Applicative ((<*>))
34 import Control.Monad (mzero)
37 import Data.Aeson.Types (emptyObject)
38 import Data.Aeson (Object, toJSON)
39 import Data.Aeson.TH (deriveJSON)
40 import Data.ByteString.Lazy (ByteString)
43 import Data.Monoid (mempty)
44 import Data.Text (Text, unpack)
45 import Data.Time (UTCTime)
48 import Text.Read (read)
49 import Text.Show (Show())
51 import Database.PostgreSQL.Simple.ToField (ToField, toField, toJSONField)
52 import Database.PostgreSQL.Simple.FromField (FromField, fromField)
55 import Test.QuickCheck.Arbitrary
56 import Test.QuickCheck (elements)
57 import Test.QuickCheck.Instances.Time ()
58 import Test.QuickCheck.Instances.Text ()
60 import Gargantext.Prelude
61 import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixSwagger)
62 import Gargantext.Viz.Phylo (Phylo)
63 --import Gargantext.Database.Utils
64 ------------------------------------------------------------------------
66 newtype NodeId = NodeId Int
67 deriving (Show, Read, Generic, Num, Eq, Ord, Enum, ToJSONKey, FromJSONKey, ToJSON, FromJSON)
69 instance ToField NodeId where
70 toField (NodeId n) = toField n
72 instance FromField NodeId where
73 fromField field mdata = do
74 n <- fromField field mdata
76 then return $ NodeId n
79 instance ToSchema NodeId
86 ------------------------------------------------------------------------
87 data NodePoly id typename userId
89 hyperdata = Node { _node_id :: id
90 , _node_typename :: typename
92 , _node_userId :: userId
93 , _node_parentId :: parentId
98 , _node_hyperdata :: hyperdata
99 } deriving (Show, Generic)
100 $(deriveJSON (unPrefix "_node_") ''NodePoly)
101 $(makeLenses ''NodePoly)
103 -- | NodePoly indicates that Node has a Polymorphism Type
104 type Node json = NodePoly NodeId NodeTypeId UserId (Maybe ParentId) NodeName UTCTime json
107 ------------------------------------------------------------------------
110 instance FromHttpApiData NodeId where
111 parseUrlPiece n = pure $ NodeId $ (read . cs) n
113 instance ToParamSchema NodeId
114 instance Arbitrary NodeId where
115 arbitrary = NodeId <$> arbitrary
117 type ParentId = NodeId
118 type CorpusId = NodeId
120 type DocumentId = NodeId
123 type MasterCorpusId = CorpusId
124 type UserCorpusId = CorpusId
126 type GraphId = NodeId
127 type PhyloId = NodeId
128 type AnnuaireId = NodeId
129 type ContactId = NodeId
132 type MasterUserId = UserId
134 id2int :: NodeId -> Int
135 id2int (NodeId n) = n
137 ------------------------------------------------------------------------
138 data Status = Status { status_failed :: !Int
139 , status_succeeded :: !Int
140 , status_remaining :: !Int
141 } deriving (Show, Generic)
142 $(deriveJSON (unPrefix "status_") ''Status)
144 instance Arbitrary Status where
145 arbitrary = Status <$> arbitrary <*> arbitrary <*> arbitrary
147 ------------------------------------------------------------------------
148 data StatusV3 = StatusV3 { statusV3_error :: !(Maybe Text)
149 , statusV3_action :: !(Maybe Text)
150 } deriving (Show, Generic)
151 $(deriveJSON (unPrefix "statusV3_") ''StatusV3)
152 ------------------------------------------------------------------------
154 -- Only Hyperdata types should be member of this type class.
156 ------------------------------------------------------------------------
157 data HyperdataDocumentV3 = HyperdataDocumentV3 { hyperdataDocumentV3_publication_day :: !(Maybe Int)
158 , hyperdataDocumentV3_language_iso2 :: !(Maybe Text)
159 , hyperdataDocumentV3_publication_second :: !(Maybe Int)
160 , hyperdataDocumentV3_publication_minute :: !(Maybe Int)
161 , hyperdataDocumentV3_publication_month :: !(Maybe Int)
162 , hyperdataDocumentV3_publication_hour :: !(Maybe Int)
163 , hyperdataDocumentV3_error :: !(Maybe Text)
164 , hyperdataDocumentV3_language_iso3 :: !(Maybe Text)
165 , hyperdataDocumentV3_authors :: !(Maybe Text)
166 , hyperdataDocumentV3_publication_year :: !(Maybe Int)
167 , hyperdataDocumentV3_publication_date :: !(Maybe Text)
168 , hyperdataDocumentV3_language_name :: !(Maybe Text)
169 , hyperdataDocumentV3_statuses :: !(Maybe [StatusV3])
170 , hyperdataDocumentV3_realdate_full_ :: !(Maybe Text)
171 , hyperdataDocumentV3_source :: !(Maybe Text)
172 , hyperdataDocumentV3_abstract :: !(Maybe Text)
173 , hyperdataDocumentV3_title :: !(Maybe Text)
174 } deriving (Show, Generic)
175 $(deriveJSON (unPrefix "hyperdataDocumentV3_") ''HyperdataDocumentV3)
178 instance Hyperdata HyperdataDocumentV3
180 ------------------------------------------------------------------------
181 data HyperdataDocument = HyperdataDocument { _hyperdataDocument_bdd :: !(Maybe Text)
182 , _hyperdataDocument_doi :: !(Maybe Text)
183 , _hyperdataDocument_url :: !(Maybe Text)
184 , _hyperdataDocument_uniqId :: !(Maybe Text)
185 , _hyperdataDocument_uniqIdBdd :: !(Maybe Text)
186 , _hyperdataDocument_page :: !(Maybe Int)
187 , _hyperdataDocument_title :: !(Maybe Text)
188 , _hyperdataDocument_authors :: !(Maybe Text)
189 , _hyperdataDocument_institutes :: !(Maybe Text)
190 , _hyperdataDocument_source :: !(Maybe Text)
191 , _hyperdataDocument_abstract :: !(Maybe Text)
192 , _hyperdataDocument_publication_date :: !(Maybe Text)
193 , _hyperdataDocument_publication_year :: !(Maybe Int)
194 , _hyperdataDocument_publication_month :: !(Maybe Int)
195 , _hyperdataDocument_publication_day :: !(Maybe Int)
196 , _hyperdataDocument_publication_hour :: !(Maybe Int)
197 , _hyperdataDocument_publication_minute :: !(Maybe Int)
198 , _hyperdataDocument_publication_second :: !(Maybe Int)
199 , _hyperdataDocument_language_iso2 :: !(Maybe Text)
200 } deriving (Show, Generic)
202 $(deriveJSON (unPrefix "_hyperdataDocument_") ''HyperdataDocument)
203 $(makeLenses ''HyperdataDocument)
205 class ToHyperdataDocument a where
206 toHyperdataDocument :: a -> HyperdataDocument
208 instance ToHyperdataDocument HyperdataDocument
210 toHyperdataDocument = identity
212 instance Eq HyperdataDocument where
213 (==) h1 h2 = (==) (_hyperdataDocument_uniqId h1) (_hyperdataDocument_uniqId h2)
215 instance Ord HyperdataDocument where
216 compare h1 h2 = compare (_hyperdataDocument_publication_date h1) (_hyperdataDocument_publication_date h2)
218 instance Hyperdata HyperdataDocument
220 instance ToField HyperdataDocument where
221 toField = toJSONField
223 instance Arbitrary HyperdataDocument where
224 arbitrary = elements arbitraryHyperdataDocuments
226 arbitraryHyperdataDocuments :: [HyperdataDocument]
227 arbitraryHyperdataDocuments =
228 map toHyperdataDocument' ([ ("AI is big but less than crypto", "Troll System journal")
229 , ("Crypto is big but less than AI", "System Troll review" )
230 , ("Science is magic" , "Closed Source review")
231 , ("Open science for all" , "No Time" )
232 , ("Closed science for me" , "No Space" )
235 toHyperdataDocument' (t1,t2) =
236 HyperdataDocument Nothing Nothing Nothing Nothing Nothing Nothing (Just t1)
237 Nothing Nothing (Just t2) Nothing Nothing Nothing Nothing Nothing
238 Nothing Nothing Nothing Nothing
240 ------------------------------------------------------------------------
241 data LanguageNodes = LanguageNodes { languageNodes___unknown__ :: [Int]}
242 deriving (Show, Generic)
243 $(deriveJSON (unPrefix "languageNodes_") ''LanguageNodes)
245 ------------------------------------------------------------------------
246 -- level: debug | dev (fatal = critical)
247 data EventLevel = CRITICAL | FATAL | ERROR | WARNING | INFO | DEBUG
248 deriving (Show, Generic, Enum, Bounded)
250 instance FromJSON EventLevel
251 instance ToJSON EventLevel
253 instance Arbitrary EventLevel where
254 arbitrary = elements [minBound..maxBound]
256 instance ToSchema EventLevel where
257 declareNamedSchema proxy = genericDeclareNamedSchema defaultSchemaOptions proxy
259 ------------------------------------------------------------------------
261 data Event = Event { event_level :: !EventLevel
262 , event_message :: !Text
263 , event_date :: !UTCTime
264 } deriving (Show, Generic)
265 $(deriveJSON (unPrefix "event_") ''Event)
267 instance Arbitrary Event where
268 arbitrary = Event <$> arbitrary <*> arbitrary <*> arbitrary
270 instance ToSchema Event where
271 declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "event_")
273 ------------------------------------------------------------------------
275 data Resource = Resource { resource_path :: !(Maybe Text)
276 , resource_scraper :: !(Maybe Text)
277 , resource_query :: !(Maybe Text)
278 , resource_events :: !([Event])
279 , resource_status :: !Status
280 , resource_date :: !UTCTime
281 } deriving (Show, Generic)
282 $(deriveJSON (unPrefix "resource_") ''Resource)
284 instance Arbitrary Resource where
285 arbitrary = Resource <$> arbitrary
292 instance ToSchema Resource where
293 declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "resource_")
295 ------------------------------------------------------------------------
296 data HyperdataUser = HyperdataUser { hyperdataUser_language :: Maybe Text
297 } deriving (Show, Generic)
298 $(deriveJSON (unPrefix "hyperdataUser_") ''HyperdataUser)
300 instance Hyperdata HyperdataUser
301 ------------------------------------------------------------------------
302 data HyperdataFolder = HyperdataFolder { hyperdataFolder_desc :: Maybe Text
303 } deriving (Show, Generic)
304 $(deriveJSON (unPrefix "hyperdataFolder_") ''HyperdataFolder)
306 instance Hyperdata HyperdataFolder
307 ------------------------------------------------------------------------
308 data HyperdataCorpus = HyperdataCorpus { hyperdataCorpus_title :: !(Maybe Text)
309 , hyperdataCorpus_desc :: !(Maybe Text)
310 , hyperdataCorpus_query :: !(Maybe Text)
311 , hyperdataCorpus_authors :: !(Maybe Text)
312 , hyperdataCorpus_resources :: !(Maybe [Resource])
313 } deriving (Show, Generic)
314 $(deriveJSON (unPrefix "hyperdataCorpus_") ''HyperdataCorpus)
316 instance Hyperdata HyperdataCorpus
318 corpusExample :: ByteString
319 corpusExample = "" -- TODO
321 defaultCorpus :: HyperdataCorpus
322 defaultCorpus = (HyperdataCorpus (Just "Title") (Just "Descr") (Just "Bool query") (Just "Authors") Nothing)
324 hyperdataCorpus :: HyperdataCorpus
325 hyperdataCorpus = case decode corpusExample of
327 Nothing -> defaultCorpus
329 instance Arbitrary HyperdataCorpus where
330 arbitrary = pure hyperdataCorpus -- TODO
332 ------------------------------------------------------------------------
334 data HyperdataList = HyperdataList {hd_list :: !(Maybe Text)
335 } deriving (Show, Generic)
336 $(deriveJSON (unPrefix "hd_") ''HyperdataList)
338 instance Hyperdata HyperdataList
340 ------------------------------------------------------------------------
341 data HyperdataAnnuaire = HyperdataAnnuaire { hyperdataAnnuaire_title :: !(Maybe Text)
342 , hyperdataAnnuaire_desc :: !(Maybe Text)
343 } deriving (Show, Generic)
344 $(deriveJSON (unPrefix "hyperdataAnnuaire_") ''HyperdataAnnuaire)
346 instance Hyperdata HyperdataAnnuaire
348 hyperdataAnnuaire :: HyperdataAnnuaire
349 hyperdataAnnuaire = HyperdataAnnuaire (Just "Annuaire Title") (Just "Annuaire Description")
351 instance Arbitrary HyperdataAnnuaire where
352 arbitrary = pure hyperdataAnnuaire -- TODO
354 ------------------------------------------------------------------------
355 newtype HyperdataAny = HyperdataAny Object
356 deriving (Show, Generic, ToJSON, FromJSON)
358 instance Hyperdata HyperdataAny
360 instance Arbitrary HyperdataAny where
361 arbitrary = pure $ HyperdataAny mempty -- TODO produce arbitrary objects
362 ------------------------------------------------------------------------
365 instance Arbitrary HyperdataList' where
366 arbitrary = elements [HyperdataList' (Just "from list A")]
370 data HyperdataListModel = HyperdataListModel { _hlm_params :: !(Int, Int)
372 , _hlm_score :: !(Maybe Double)
373 } deriving (Show, Generic)
375 instance Hyperdata HyperdataListModel
376 instance Arbitrary HyperdataListModel where
377 arbitrary = elements [HyperdataListModel (100,100) "models/example.model" Nothing]
379 $(deriveJSON (unPrefix "_hlm_") ''HyperdataListModel)
380 $(makeLenses ''HyperdataListModel)
382 ------------------------------------------------------------------------
383 data HyperdataScore = HyperdataScore { hyperdataScore_preferences :: !(Maybe Text)
384 } deriving (Show, Generic)
385 $(deriveJSON (unPrefix "hyperdataScore_") ''HyperdataScore)
387 instance Hyperdata HyperdataScore
389 ------------------------------------------------------------------------
391 data HyperdataResource = HyperdataResource { hyperdataResource_preferences :: !(Maybe Text)
392 } deriving (Show, Generic)
393 $(deriveJSON (unPrefix "hyperdataResource_") ''HyperdataResource)
395 instance Hyperdata HyperdataResource
397 ------------------------------------------------------------------------
398 data HyperdataDashboard = HyperdataDashboard { hyperdataDashboard_preferences :: !(Maybe Text)
399 } deriving (Show, Generic)
400 $(deriveJSON (unPrefix "hyperdataDashboard_") ''HyperdataDashboard)
402 instance Hyperdata HyperdataDashboard
404 ------------------------------------------------------------------------
406 -- TODO add the Graph Structure here
407 data HyperdataPhylo = HyperdataPhylo { hyperdataPhylo_preferences :: !(Maybe Text)
408 , hyperdataPhylo_data :: !(Maybe Phylo)
409 } deriving (Show, Generic)
410 $(deriveJSON (unPrefix "hyperdataPhylo_") ''HyperdataPhylo)
412 instance Hyperdata HyperdataPhylo
414 ------------------------------------------------------------------------
415 -- | TODO FEATURE: Notebook saved in the node
416 data HyperdataNotebook = HyperdataNotebook { hyperdataNotebook_preferences :: !(Maybe Text)
417 } deriving (Show, Generic)
418 $(deriveJSON (unPrefix "hyperdataNotebook_") ''HyperdataNotebook)
420 instance Hyperdata HyperdataNotebook
424 data HyperData = HyperdataTexts { hd_preferences :: Maybe Text }
425 | HyperdataList' { hd_preferences :: Maybe Text}
426 deriving (Show, Generic)
428 $(deriveJSON (unPrefix "hd_") ''HyperData)
430 instance Hyperdata HyperData
434 ------------------------------------------------------------------------
435 -- | Then a Node can be either a Folder or a Corpus or a Document
436 data NodeType = NodeUser
438 | NodeFolderShared | NodeTeam
442 | NodeCorpus | NodeCorpusV3 | NodeTexts | NodeDocument
443 | NodeAnnuaire | NodeContact
444 | NodeGraph | NodePhylo
445 | NodeDashboard | NodeChart | NodeNoteBook
446 | NodeList | NodeListModel
447 deriving (Show, Read, Eq, Generic, Bounded, Enum)
456 allNodeTypes :: [NodeType]
457 allNodeTypes = [minBound ..]
459 instance FromJSON NodeType
460 instance ToJSON NodeType
462 instance FromHttpApiData NodeType
464 parseUrlPiece = Right . read . unpack
466 instance ToParamSchema NodeType
467 instance ToSchema NodeType
470 data NodePolySearch id typename userId
472 hyperdata search = NodeSearch { _ns_id :: id
473 , _ns_typename :: typename
474 , _ns_userId :: userId
475 -- , nodeUniqId :: shaId
476 , _ns_parentId :: parentId
480 , _ns_hyperdata :: hyperdata
481 , _ns_search :: search
482 } deriving (Show, Generic)
483 $(deriveJSON (unPrefix "_ns_") ''NodePolySearch)
484 $(makeLenses ''NodePolySearch)
486 type NodeSearch json = NodePolySearch NodeId NodeTypeId UserId (Maybe ParentId) NodeName UTCTime json (Maybe TSVector)
487 ------------------------------------------------------------------------
490 instance (Arbitrary hyperdata
492 ,Arbitrary nodeTypeId
494 ,Arbitrary nodeParentId
495 ) => Arbitrary (NodePoly nodeId nodeTypeId userId nodeParentId
496 NodeName UTCTime hyperdata) where
497 --arbitrary = Node 1 1 (Just 1) 1 "name" (jour 2018 01 01) (arbitrary) (Just "")
498 arbitrary = Node <$> arbitrary <*> arbitrary <*> arbitrary
499 <*> arbitrary <*> arbitrary <*> arbitrary
502 instance (Arbitrary hyperdata
504 ,Arbitrary nodeTypeId
506 ,Arbitrary nodeParentId
507 ) => Arbitrary (NodePolySearch nodeId nodeTypeId userId nodeParentId
508 NodeName UTCTime hyperdata (Maybe TSVector)) where
509 --arbitrary = Node 1 1 (Just 1) 1 "name" (jour 2018 01 01) (arbitrary) (Just "")
510 arbitrary = NodeSearch <$> arbitrary <*> arbitrary <*> arbitrary
511 <*> arbitrary <*> arbitrary <*> arbitrary
512 <*> arbitrary <*> arbitrary
515 ------------------------------------------------------------------------
516 hyperdataDocument :: HyperdataDocument
517 hyperdataDocument = case decode docExample of
519 Nothing -> HyperdataDocument Nothing Nothing Nothing Nothing
520 Nothing Nothing Nothing Nothing
521 Nothing Nothing Nothing Nothing
522 Nothing Nothing Nothing Nothing
523 Nothing Nothing Nothing
524 docExample :: ByteString
525 docExample = "{\"doi\":\"sdfds\",\"publication_day\":6,\"language_iso2\":\"en\",\"publication_minute\":0,\"publication_month\":7,\"language_iso3\":\"eng\",\"publication_second\":0,\"authors\":\"Nils Hovdenak, Kjell Haram\",\"publication_year\":2012,\"publication_date\":\"2012-07-06 00:00:00+00:00\",\"language_name\":\"English\",\"realdate_full_\":\"2012 01 12\",\"source\":\"European journal of obstetrics, gynecology, and reproductive biology\",\"abstract\":\"The literature was searched for publications on minerals and vitamins during pregnancy and the possible influence of supplements on pregnancy outcome.\",\"title\":\"Influence of mineral and vitamin supplements on pregnancy outcome.\",\"publication_hour\":0}"
527 instance ToSchema HyperdataCorpus where
528 declareNamedSchema proxy =
529 genericDeclareNamedSchema (unPrefixSwagger "hyperdataCorpus_") proxy
530 & mapped.schema.description ?~ "a corpus"
531 & mapped.schema.example ?~ toJSON hyperdataCorpus
533 instance ToSchema HyperdataAnnuaire where
534 declareNamedSchema proxy =
535 genericDeclareNamedSchema (unPrefixSwagger "hyperdataAnnuaire_") proxy
536 & mapped.schema.description ?~ "an annuaire"
537 & mapped.schema.example ?~ toJSON hyperdataAnnuaire
539 instance ToSchema HyperdataDocument where
540 declareNamedSchema proxy =
541 genericDeclareNamedSchema (unPrefixSwagger "_hyperdataDocument_") proxy
542 & mapped.schema.description ?~ "a document"
543 & mapped.schema.example ?~ toJSON hyperdataDocument
545 instance ToSchema HyperdataAny where
546 declareNamedSchema proxy =
547 pure $ genericNameSchema defaultSchemaOptions proxy mempty
548 & schema.description ?~ "a node"
549 & schema.example ?~ emptyObject -- TODO
552 instance ToSchema hyperdata =>
553 ToSchema (NodePoly NodeId NodeTypeId
558 declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_node_")
560 instance ToSchema hyperdata =>
561 ToSchema (NodePoly NodeId NodeTypeId
563 (Maybe ParentId) NodeName
566 declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_node_")
569 instance ToSchema hyperdata =>
570 ToSchema (NodePolySearch NodeId NodeTypeId
573 UTCTime hyperdata (Maybe TSVector)
575 declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_ns_")
577 instance ToSchema hyperdata =>
578 ToSchema (NodePolySearch NodeId NodeTypeId
580 (Maybe ParentId) NodeName
581 UTCTime hyperdata (Maybe TSVector)
583 declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_ns_")
586 instance ToSchema Status where
587 declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "status_")