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

-}

{-# LANGUAGE NoImplicitPrelude #-}
13 14 15 16 17 18 19 20
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE Arrows #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}


21
module Gargantext.Database.Schema.NodeNodeNgram where
22 23 24 25 26

import Prelude
import Data.Maybe (Maybe)
import Data.Profunctor.Product.TH (makeAdaptorAndInstance)
import Control.Lens.TH (makeLensesWith, abbreviatedFields)
27
import Gargantext.Database.Utils (Cmd, runOpaQuery)
28 29 30 31 32 33 34 35 36 37 38 39

import Opaleye


data NodeNodeNgramPoly node1_id node2_id ngram_id score
                   = NodeNodeNgram { nodeNodeNgram_node1_id :: node1_id
                                   , nodeNodeNgram_node2_id :: node2_id
                                   , nodeNodeNgram_ngram_id :: ngram_id
                                   , nodeNodeNgram_score   :: score
                                   } deriving (Show)


Alexandre Delanoë's avatar
Alexandre Delanoë committed
40 41 42 43
type NodeNodeNgramWrite = NodeNodeNgramPoly (Column PGInt4          )
                                            (Column PGInt4          )
                                            (Column PGInt4          )
                                            (Maybe (Column PGFloat8))
44

Alexandre Delanoë's avatar
Alexandre Delanoë committed
45 46 47 48 49 50 51 52 53 54 55 56 57 58
type NodeNodeNgramRead  = NodeNodeNgramPoly (Column PGInt4  )
                                            (Column PGInt4  )
                                            (Column PGInt4  )
                                            (Column PGFloat8)

type NodeNodeNgramReadNull  = NodeNodeNgramPoly (Column (Nullable PGInt4  ))
                                                (Column (Nullable PGInt4  ))
                                                (Column (Nullable PGInt4  ))
                                                (Column (Nullable PGFloat8))

type NodeNodeNgram = NodeNodeNgramPoly Int
                                       Int
                                       Int 
                                (Maybe Double)
59 60 61 62 63 64


$(makeAdaptorAndInstance "pNodeNodeNgram" ''NodeNodeNgramPoly)
$(makeLensesWith abbreviatedFields        ''NodeNodeNgramPoly)

nodeNodeNgramTable :: Table NodeNodeNgramWrite NodeNodeNgramRead
Alexandre Delanoë's avatar
Alexandre Delanoë committed
65 66 67 68 69 70 71 72
nodeNodeNgramTable  = Table "nodes_nodes_ngrams" 
                          ( pNodeNodeNgram NodeNodeNgram
                               { nodeNodeNgram_node1_id = required "node1_id"
                               , nodeNodeNgram_node2_id = required "node2_id"
                               , nodeNodeNgram_ngram_id = required "ngram_id"
                               , nodeNodeNgram_score    = optional "score"
                               }
                          )
73 74 75 76 77 78


queryNodeNodeNgramTable :: Query NodeNodeNgramRead
queryNodeNodeNgramTable = queryTable nodeNodeNgramTable

-- | not optimized (get all ngrams without filters)
79 80
nodeNodeNgrams :: Cmd err [NodeNodeNgram]
nodeNodeNgrams = runOpaQuery queryNodeNodeNgramTable
81 82 83

instance QueryRunnerColumnDefault PGFloat8 (Maybe Double) where
    queryRunnerColumnDefault = fieldQueryRunnerColumn