Commit 6a8cadda authored by Alexandre Delanoë's avatar Alexandre Delanoë

[Database.Schema] NodeNode_NodeNode table

parent 867e7c47
...@@ -72,8 +72,6 @@ CREATE TABLE public.node_nodengrams_nodengrams ( ...@@ -72,8 +72,6 @@ CREATE TABLE public.node_nodengrams_nodengrams (
); );
ALTER TABLE public.node_nodengrams_nodengrams OWNER TO gargantua; ALTER TABLE public.node_nodengrams_nodengrams OWNER TO gargantua;
-------------------------------------------------------------- --------------------------------------------------------------
-------------------------------------------------------------- --------------------------------------------------------------
-- --
......
{-|
Module : Gargantext.Database.Query.Table.NodeNode_NodeNode
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# LANGUAGE Arrows #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-}
module Gargantext.Database.Query.Table.NodeNode
where
import Control.Arrow (returnA)
import Control.Lens (view, (^.))
import Data.Maybe (catMaybes)
import Data.Text (Text, splitOn)
import Database.PostgreSQL.Simple.SqlQQ (sql)
import Database.PostgreSQL.Simple.Types (Values(..), QualifiedIdentifier(..))
import qualified Database.PostgreSQL.Simple as PGS (Query, Only(..))
import qualified Opaleye as O
import Opaleye
import Gargantext.Core.Types
import Gargantext.Database.Schema.NodeNode_NodeNode
import Gargantext.Database.Admin.Config (nodeTypeId)
import Gargantext.Database.Admin.Types.Hyperdata
import Gargantext.Database.Admin.Types.Node (CorpusId, DocId, pgNodeId)
import Gargantext.Database.Prelude
import Gargantext.Database.Schema.Node
import Gargantext.Prelude
queryNodeNode_NodeNodeTable :: Query NodeNode_NodeNodeRead
queryNodeNode_NodeNodeTable = queryTable nodeNode_NodeNodeTable
------------------------------------------------------------------------
insertNodeNode_NodeNode :: [NodeNode_NodeNode] -> Cmd err Int64
insertNodeNode_NodeNode ns = mkCmd $ \conn -> runInsert_ conn
$ Insert nodeNode_NodeNodeTable ns' rCount Nothing
where
ns' :: [NodeNode_NodeNodeWrite]
ns' = map (\(NodeNode_NodeNode nn1 nn2 w)
-> NodeNode_NodeNode (pgInt4 nn1)
(pgInt4 nn1)
(pgDouble <$> x)
) ns
------------------------------------------------------------------------
-- | TODO delete
--
------------------------------------------------------------------------
{-|
Module : Gargantext.Database.Schema.NodeNode_NodeNode
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# LANGUAGE Arrows #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-}
module Gargantext.Database.Schema.NodeNode where
import Data.Maybe (Maybe)
import Gargantext.Core.Types
import Gargantext.Database.Schema.Prelude
import Gargantext.Prelude
data NodeNode_NodeNodePoly nn1 nn2 weight
= NodeNode_NodeNode { _nnnn_nn1_id :: !nn1
, _nnnn_nn2_id :: !nn2
, _nnnn_weight :: !weight
} deriving (Show)
type NodeNodeWrite = NodeNodePoly (Column (PGInt4))
(Column (PGInt4))
(Maybe (Column (PGFloat8)))
type NodeNodeRead = NodeNodePoly (Column (PGInt4))
(Column (PGInt4))
(Maybe (Column (PGFloat8)))
type NodeNodeReadNull = NodeNodePoly (Column (Nullable PGInt4))
(Column (Nullable PGInt4))
(Column (Nullable PGFloat8))
type NodeNode_NodeNode = NodeNode_NodeNodePoly Int Int (Maybe Double)
$(makeAdaptorAndInstance "pNodeNode_NodeNode" ''NodeNode_NodeNodePoly)
makeLenses ''NodeNode_NodeNodePoly
nodeNode_NodeNodeTable :: Table NodeNode_NodeNodeWrite NodeNode_NodeNodeRead
nodeNode_NodeNodeTable =
Table "nodesnodes_nodesnodes"
( pNodeNode_NodeNode
NodeNode_NodeNode { _nnnn_nn1_id = required "nn1_id"
, _nnnn_nn2_id = required "nn2_id"
, _nnnn_weight = optional "weight"
}
)
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment