NodeNodeNgrams.hs 3.82 KB
Newer Older
1
{-|
2
Module      : Gargantext.Database.Schema.NodeNodeNgrams
3
Description : TODO: remove this module and table in database
4 5 6 7 8 9 10 11
Copyright   : (c) CNRS, 2017-Present
License     : AGPL + CECILL v3
Maintainer  : team@gargantext.org
Stability   : experimental
Portability : POSIX

-}

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

14 15 16 17 18 19 20
{-# LANGUAGE Arrows                 #-}
{-# LANGUAGE FlexibleInstances      #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE MultiParamTypeClasses  #-}
{-# LANGUAGE NoImplicitPrelude      #-}
{-# LANGUAGE RankNTypes             #-}
{-# LANGUAGE TemplateHaskell        #-}
21

22 23
module Gargantext.Database.Schema.NodeNodeNgrams
  where
24 25 26

import Prelude
import Data.Profunctor.Product.TH (makeAdaptorAndInstance)
27
import Control.Lens.TH (makeLenses)
28 29 30 31
import Gargantext.Database.Utils (Cmd, mkCmd)
import Gargantext.Database.Schema.Ngrams (NgramsTypeId, pgNgramsTypeId, NgramsId)
import Gargantext.Database.Schema.Node (pgNodeId)
import Gargantext.Database.Types.Node
32 33
import Opaleye

34 35
data NodeNodeNgramsPoly n1 n2 ngrams_id ngt w
   = NodeNodeNgrams { _nnng_node1_id   :: n1
36 37 38 39
                    , _nnng_node2_id   :: n2
                    , _nnng_ngrams_id  :: ngrams_id
                    , _nnng_ngramsType :: ngt
                    , _nnng_weight     :: w
40 41 42
                    } deriving (Show)

type NodeNodeNgramsWrite =
43
     NodeNodeNgramsPoly (Column PGInt4  )
44 45 46 47 48 49 50 51 52 53 54 55 56 57 58 59 60 61 62 63
                        (Column PGInt4  )
                        (Column PGInt4  )
                        (Column PGInt4  )
                        (Column PGFloat8)

type NodeNodeNgramsRead  =
     NodeNodeNgramsPoly (Column PGInt4  )
                        (Column PGInt4  )
                        (Column PGInt4  )
                        (Column PGInt4  )
                        (Column PGFloat8)

type NodeNodeNgramsReadNull =
     NodeNodeNgramsPoly (Column (Nullable PGInt4  ))
                        (Column (Nullable PGInt4  ))
                        (Column (Nullable PGInt4  ))
                        (Column (Nullable PGInt4  ))
                        (Column (Nullable PGFloat8))

type NodeNodeNgrams =
64
  NodeNodeNgramsPoly CorpusId DocId NgramsId NgramsTypeId Double
65

66
$(makeAdaptorAndInstance "pNodeNodeNgrams" ''NodeNodeNgramsPoly)
67 68
makeLenses ''NodeNodeNgramsPoly

69

70
nodeNodeNgramsTable :: Table NodeNodeNgramsWrite NodeNodeNgramsRead
71
nodeNodeNgramsTable  = Table "node_node_ngrams"
72
                          ( pNodeNodeNgrams NodeNodeNgrams
73
                               { _nnng_node1_id   = required "node1_id"
74 75 76 77
                               , _nnng_node2_id   = required "node2_id"
                               , _nnng_ngrams_id  = required "ngrams_id"
                               , _nnng_ngramsType = required "ngrams_type"
                               , _nnng_weight     = required "weight"
Alexandre Delanoë's avatar
Alexandre Delanoë committed
78 79
                               }
                          )
80

81 82
queryNodeNodeNgramsTable :: Query NodeNodeNgramsRead
queryNodeNodeNgramsTable = queryTable nodeNodeNgramsTable
83

84 85 86
-- | Insert utils
insertNodeNodeNgrams :: [NodeNodeNgrams] -> Cmd err Int
insertNodeNodeNgrams = insertNodeNodeNgramsW
87 88
                     . map (\(NodeNodeNgrams n1 n2 ng nt w) ->
                              NodeNodeNgrams (pgNodeId n1)
89 90 91 92 93 94 95 96 97 98 99 100 101 102 103 104
                                             (pgNodeId n2)
                                             (pgInt4   ng)
                                             (pgNgramsTypeId nt)
                                             (pgDouble w)
                                                  )

insertNodeNodeNgramsW :: [NodeNodeNgramsWrite] -> Cmd err Int
insertNodeNodeNgramsW nnnw =
  mkCmd $ \c -> fromIntegral <$> runInsert_ c insertNothing
    where
      insertNothing = (Insert { iTable = nodeNodeNgramsTable
                              , iRows  = nnnw
                              , iReturning = rCount
                              , iOnConflict = (Just DoNothing)
      })