NodeNgrams.hs 4.58 KB
Newer Older
1 2 3 4 5 6 7 8 9
{-|
Module      : Gargantext.Database.Schema.NodeNgrams
Description : 
Copyright   : (c) CNRS, 2017-Present
License     : AGPL + CECILL v3
Maintainer  : team@gargantext.org
Stability   : experimental
Portability : POSIX

10 11
NodeNgrams register Context of Ngrams (named Cgrams then)

12 13 14 15 16 17 18 19 20
-}

{-# OPTIONS_GHC -fno-warn-orphans #-}

{-# LANGUAGE Arrows                 #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE QuasiQuotes            #-}
{-# LANGUAGE TemplateHaskell        #-}

21
module Gargantext.Database.Schema.NodeNgrams where
22 23 24

import Data.Text (Text)
import Gargantext.Core.Types
25
import Gargantext.Database.Schema.Ngrams (NgramsType)
26
import Gargantext.Database.Schema.Prelude
27 28
import Gargantext.Prelude

29

30 31 32 33 34 35 36 37 38
data NodeNgramsPoly id
                    node_id'
                    node_subtype
                    ngrams_id
                    ngrams_type
                    ngrams_field
                    ngrams_tag
                    ngrams_class
                    weight
Alexandre Delanoë's avatar
Alexandre Delanoë committed
39 40 41 42 43 44 45 46 47
                   = NodeNgrams { _nng_id            :: !id
                                , _nng_node_id       :: !node_id'
                                , _nng_node_subtype  :: !node_subtype
                                , _nng_ngrams_id     :: !ngrams_id
                                , _nng_ngrams_type   :: !ngrams_type
                                , _nng_ngrams_field  :: !ngrams_field
                                , _nng_ngrams_tag    :: !ngrams_tag
                                , _nng_ngrams_class  :: !ngrams_class
                                , _nng_ngrams_weight :: !weight
Alexandre Delanoë's avatar
Alexandre Delanoë committed
48
                              } deriving (Show, Eq, Ord)
49

50

51 52 53 54 55 56 57 58 59
type NodeNgramsWrite = NodeNgramsPoly (Maybe (Column (SqlInt4)))
                                      (Column (SqlInt4))
                                      (Maybe  (Column (SqlInt4)))
                                      (Column (SqlInt4))
                                      (Maybe  (Column (SqlInt4)))
                                      (Maybe  (Column (SqlInt4)))
                                      (Maybe  (Column (SqlInt4)))
                                      (Maybe  (Column (SqlInt4)))
                                      (Maybe  (Column (SqlFloat8)))
60

61
type NodeNgramsRead    = NodeNgramsPoly (Column SqlInt4)
62 63 64 65 66 67 68 69
                                      (Column SqlInt4)
                                      (Column SqlInt4)
                                      (Column SqlInt4)
                                      (Column SqlInt4)
                                      (Column SqlInt4)
                                      (Column SqlInt4)
                                      (Column SqlInt4)
                                      (Column SqlFloat8)
70

71

72 73 74 75
type NodeNgramsReadNull = NodeNgramsPoly (Column (Nullable SqlInt4))
                                         (Column (Nullable SqlInt4))
                                         (Column (Nullable SqlInt4))
                                         (Column (Nullable SqlInt4))
76

77 78 79 80 81
                                         (Column (Nullable SqlInt4))
                                         (Column (Nullable SqlInt4))
                                         (Column (Nullable SqlInt4))
                                         (Column (Nullable SqlInt4))
                                         (Column (Nullable SqlFloat8))
82 83 84 85 86
type NodeNgramsId = Int
type NgramsField  = Int
type NgramsTag    = Int
type NgramsClass  = Int
type NgramsText   = Text
87 88 89 90 91

-- Example of list Ngrams
-- type ListNgrams = NodeNgramsPoly (Maybe Int) ListType Text 

type NodeNgramsW =
92
  NodeNgramsPoly (Maybe NodeNgramsId) NodeId ListType NgramsText
93 94 95
                  NgramsType (Maybe NgramsField) (Maybe NgramsTag) (Maybe NgramsClass)
                  Double

96 97 98 99 100 101 102 103 104 105 106 107 108 109 110 111 112 113
$(makeAdaptorAndInstance "pNodeNgrams" ''NodeNgramsPoly)
makeLenses ''NodeNgramsPoly

nodeNgramsTable :: Table NodeNgramsWrite NodeNgramsRead
nodeNgramsTable  =
  Table "node_ngrams"
         ( pNodeNgrams
           NodeNgrams { _nng_id            = optionalTableField "id"
                      , _nng_node_id       = requiredTableField "node_id"
                      , _nng_node_subtype  = optionalTableField "node_subtype"
                      , _nng_ngrams_id     = requiredTableField "ngrams_id"
                      , _nng_ngrams_type   = optionalTableField "ngrams_type"
                      , _nng_ngrams_field  = optionalTableField "ngrams_field"
                      , _nng_ngrams_tag    = optionalTableField "ngrams_tag"
                      , _nng_ngrams_class  = optionalTableField "ngrams_class"
                      , _nng_ngrams_weight = optionalTableField "weight"
                      }
                  )