Commit a759d5d6 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[NewType] Merge, NodeNgram* fix.

parents 6cacf848 3e2fa028
...@@ -83,7 +83,7 @@ import Gargantext.API.Node ( GargServer ...@@ -83,7 +83,7 @@ import Gargantext.API.Node ( GargServer
, HyperdataAnnuaire , HyperdataAnnuaire
) )
--import Gargantext.Database.Node.Contact (HyperdataContact) --import Gargantext.Database.Node.Contact (HyperdataContact)
import Gargantext.Database.Types.Node () import Gargantext.Database.Types.Node (NodeId, CorpusId, AnnuaireId)
import Gargantext.API.Count ( CountAPI, count, Query) import Gargantext.API.Count ( CountAPI, count, Query)
import Gargantext.API.Search ( SearchAPI, search, SearchQuery) import Gargantext.API.Search ( SearchAPI, search, SearchQuery)
import Gargantext.Database.Facet import Gargantext.Database.Facet
...@@ -222,19 +222,19 @@ type GargAPI' = ...@@ -222,19 +222,19 @@ type GargAPI' =
-- Node endpoint -- Node endpoint
:<|> "node" :> Summary "Node endpoint" :<|> "node" :> Summary "Node endpoint"
:> Capture "id" Int :> NodeAPI HyperdataAny :> Capture "id" NodeId :> NodeAPI HyperdataAny
-- Corpus endpoint -- Corpus endpoint
:<|> "corpus":> Summary "Corpus endpoint" :<|> "corpus":> Summary "Corpus endpoint"
:> Capture "id" Int :> NodeAPI HyperdataCorpus :> Capture "id" CorpusId :> NodeAPI HyperdataCorpus
-- Annuaire endpoint -- Annuaire endpoint
:<|> "annuaire":> Summary "Annuaire endpoint" :<|> "annuaire":> Summary "Annuaire endpoint"
:> Capture "id" Int :> NodeAPI HyperdataAnnuaire :> Capture "id" AnnuaireId :> NodeAPI HyperdataAnnuaire
-- Corpus endpoint -- Corpus endpoint
:<|> "nodes" :> Summary "Nodes endpoint" :<|> "nodes" :> Summary "Nodes endpoint"
:> ReqBody '[JSON] [Int] :> NodesAPI :> ReqBody '[JSON] [NodeId] :> NodesAPI
-- :<|> "counts" :> Stream GET NewLineFraming '[JSON] Count :> CountAPI -- :<|> "counts" :> Stream GET NewLineFraming '[JSON] Count :> CountAPI
-- Corpus endpoint -- Corpus endpoint
...@@ -250,11 +250,11 @@ type GargAPI' = ...@@ -250,11 +250,11 @@ type GargAPI' =
:> SearchAPI :> SearchAPI
:<|> "graph" :> Summary "Graph endpoint" :<|> "graph" :> Summary "Graph endpoint"
:> Capture "id" Int :> GraphAPI :> Capture "id" NodeId :> GraphAPI
-- Tree endpoint -- Tree endpoint
:<|> "tree" :> Summary "Tree endpoint" :<|> "tree" :> Summary "Tree endpoint"
:> Capture "id" Int :> TreeAPI :> Capture "id" NodeId :> TreeAPI
-- :<|> "scraper" :> WithCallbacks ScraperAPI -- :<|> "scraper" :> WithCallbacks ScraperAPI
......
...@@ -35,7 +35,7 @@ import Data.Text (Text, reverse) ...@@ -35,7 +35,7 @@ import Data.Text (Text, reverse)
import GHC.Generics (Generic) import GHC.Generics (Generic)
import Gargantext.Core.Utils.Prefix (unPrefix) import Gargantext.Core.Utils.Prefix (unPrefix)
import Gargantext.Database.Root (getRoot) import Gargantext.Database.Root (getRoot)
import Gargantext.Database.Types.Node (NodePoly(_node_id)) import Gargantext.Database.Types.Node (NodePoly(_node_id), NodeId)
import Gargantext.Database.Utils (Cmd) import Gargantext.Database.Utils (Cmd)
import Gargantext.Prelude hiding (reverse) import Gargantext.Prelude hiding (reverse)
import Test.QuickCheck (elements, oneof) import Test.QuickCheck (elements, oneof)
...@@ -67,7 +67,7 @@ data AuthValid = AuthValid { _authVal_token :: Token ...@@ -67,7 +67,7 @@ data AuthValid = AuthValid { _authVal_token :: Token
deriving (Generic) deriving (Generic)
type Token = Text type Token = Text
type TreeId = Int type TreeId = NodeId
-- | Main functions of authorization -- | Main functions of authorization
......
...@@ -62,7 +62,8 @@ import Gargantext.API.Search ( SearchAPI, searchIn, SearchInQuery) ...@@ -62,7 +62,8 @@ import Gargantext.API.Search ( SearchAPI, searchIn, SearchInQuery)
import Gargantext.Viz.Graph hiding (Node)-- (Graph(_graph_metadata),LegendField(..), GraphMetadata(..),readGraphFromJson,defaultGraph) import Gargantext.Viz.Graph hiding (Node)-- (Graph(_graph_metadata),LegendField(..), GraphMetadata(..),readGraphFromJson,defaultGraph)
-- import Gargantext.Core (Lang(..)) -- import Gargantext.Core (Lang(..))
import Gargantext.Core.Types (Offset, Limit) import Gargantext.Core.Types (Offset, Limit)
import Gargantext.Core.Types.Main (Tree, NodeTree, CorpusId, ContactId) import Gargantext.Core.Types.Main (Tree, NodeTree)
import Gargantext.Database.Types.Node (CorpusId, ContactId)
-- import Gargantext.Text.Terms (TermType(..)) -- import Gargantext.Text.Terms (TermType(..))
import Test.QuickCheck (elements) import Test.QuickCheck (elements)
...@@ -117,13 +118,13 @@ type NodeAPI a = Get '[JSON] (Node a) ...@@ -117,13 +118,13 @@ type NodeAPI a = Get '[JSON] (Node a)
:> QueryParam "order" OrderBy :> QueryParam "order" OrderBy
:> SearchAPI :> SearchAPI
type RenameApi = Summary " RenameNode Node" type RenameApi = Summary " Rename Node"
:> ReqBody '[JSON] RenameNode :> ReqBody '[JSON] RenameNode
:> Put '[JSON] [Int] :> Put '[JSON] [Int]
type PostNodeApi = Summary " PostNode Node with ParentId as {id}" type PostNodeApi = Summary " PostNode Node with ParentId as {id}"
:> ReqBody '[JSON] PostNode :> ReqBody '[JSON] PostNode
:> Post '[JSON] [Int] :> Post '[JSON] [NodeId]
type ChildrenApi a = Summary " Summary children" type ChildrenApi a = Summary " Summary children"
:> QueryParam "type" NodeType :> QueryParam "type" NodeType
...@@ -322,7 +323,7 @@ getChart :: NodeId -> Maybe UTCTime -> Maybe UTCTime ...@@ -322,7 +323,7 @@ getChart :: NodeId -> Maybe UTCTime -> Maybe UTCTime
-> Cmd err [FacetChart] -> Cmd err [FacetChart]
getChart _ _ _ = undefined -- TODO getChart _ _ _ = undefined -- TODO
postNode :: NodeId -> PostNode -> Cmd err [Int] postNode :: NodeId -> PostNode -> Cmd err [NodeId]
postNode pId (PostNode name nt) = mk nt (Just pId) name postNode pId (PostNode name nt) = mk nt (Just pId) name
putNode :: NodeId -> Cmd err Int putNode :: NodeId -> Cmd err Int
......
...@@ -45,7 +45,7 @@ import Gargantext.Database.Utils (Cmd) ...@@ -45,7 +45,7 @@ import Gargantext.Database.Utils (Cmd)
-- | SearchIn [NodesId] if empty then global search -- | SearchIn [NodesId] if empty then global search
-- TODO [Int] -- TODO [Int]
data SearchQuery = SearchQuery { sq_query :: [Text] data SearchQuery = SearchQuery { sq_query :: [Text]
, sq_corpus_id :: Int , sq_corpus_id :: NodeId
} deriving (Generic) } deriving (Generic)
$(deriveJSON (unPrefix "sq_") ''SearchQuery) $(deriveJSON (unPrefix "sq_") ''SearchQuery)
instance ToSchema SearchQuery where instance ToSchema SearchQuery where
......
...@@ -42,7 +42,7 @@ import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary) ...@@ -42,7 +42,7 @@ import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary)
------------------------------------------------------------------------ ------------------------------------------------------------------------
data NodeTree = NodeTree { _nt_name :: Text data NodeTree = NodeTree { _nt_name :: Text
, _nt_type :: NodeType , _nt_type :: NodeType
, _nt_id :: Int , _nt_id :: NodeId
} deriving (Show, Read, Generic) } deriving (Show, Read, Generic)
$(deriveJSON (unPrefix "_nt_") ''NodeTree) $(deriveJSON (unPrefix "_nt_") ''NodeTree)
...@@ -80,24 +80,9 @@ corpusTree nId t = TreeN (NodeTree ("Corpus " <> t) NodeCorpus nId) ( [ leafT ...@@ -80,24 +80,9 @@ corpusTree nId t = TreeN (NodeTree ("Corpus " <> t) NodeCorpus nId) ( [ leafT
--data Classification = Favorites | MyClassifcation --data Classification = Favorites | MyClassifcation
type UserId = Int
type MasterUserId = Int
type RootId = Int
type MasterCorpusId = Int
type HashId = Text type HashId = Text
type AnnuaireId = NodeId
type ContactId = NodeId
type CorpusId = NodeId
type DocumentId = NodeId
type DocId = DocumentId -- todo: remove this
type ListId = NodeId
type TypeId = Int type TypeId = Int
-- TODO multiple ListType declaration, remove it -- TODO multiple ListType declaration, remove it
data ListType = StopList | CandidateList | GraphList data ListType = StopList | CandidateList | GraphList
deriving (Generic, Eq, Ord, Show, Enum, Bounded) deriving (Generic, Eq, Ord, Show, Enum, Bounded)
...@@ -152,7 +137,6 @@ type TirankGlobal = Tficf ...@@ -152,7 +137,6 @@ type TirankGlobal = Tficf
type ErrorMessage = Text type ErrorMessage = Text
-- Queries -- Queries
type ParentId = NodeId
type Limit = Int type Limit = Int
type Offset = Int type Offset = Int
......
...@@ -219,7 +219,7 @@ viewAuthorsDoc cId _ nt = proc () -> do ...@@ -219,7 +219,7 @@ viewAuthorsDoc cId _ nt = proc () -> do
-- restrict -< nodeNode_delete nn .== (pgBool t) -- restrict -< nodeNode_delete nn .== (pgBool t)
-} -}
restrict -< _node_id contact .== (toNullable $ pgInt4 cId) restrict -< _node_id contact .== (toNullable $ pgNodeId cId)
restrict -< _node_typename doc .== (pgInt4 $ nodeTypeId nt) restrict -< _node_typename doc .== (pgInt4 $ nodeTypeId nt)
returnA -< FacetDoc (_node_id doc) (_node_date doc) (_node_name doc) (_node_hyperdata doc) (pgBool True) (pgInt4 1) returnA -< FacetDoc (_node_id doc) (_node_date doc) (_node_name doc) (_node_hyperdata doc) (pgBool True) (pgInt4 1)
...@@ -255,7 +255,7 @@ viewDocuments cId t ntId = proc () -> do ...@@ -255,7 +255,7 @@ viewDocuments cId t ntId = proc () -> do
n <- queryNodeTable -< () n <- queryNodeTable -< ()
nn <- queryNodeNodeTable -< () nn <- queryNodeNodeTable -< ()
restrict -< _node_id n .== nodeNode_node2_id nn restrict -< _node_id n .== nodeNode_node2_id nn
restrict -< nodeNode_node1_id nn .== (pgInt4 cId) restrict -< nodeNode_node1_id nn .== (pgNodeId cId)
restrict -< _node_typename n .== (pgInt4 ntId) restrict -< _node_typename n .== (pgInt4 ntId)
restrict -< nodeNode_delete nn .== (pgBool t) restrict -< nodeNode_delete nn .== (pgBool t)
returnA -< FacetDoc (_node_id n) (_node_date n) (_node_name n) (_node_hyperdata n) (nodeNode_favorite nn) (pgInt4 1) returnA -< FacetDoc (_node_id n) (_node_date n) (_node_name n) (_node_hyperdata n) (nodeNode_favorite nn) (pgInt4 1)
......
...@@ -42,8 +42,7 @@ import Gargantext.Database.Schema.Node (mkRoot, mkCorpus, getOrMkList, mkGraph, ...@@ -42,8 +42,7 @@ import Gargantext.Database.Schema.Node (mkRoot, mkCorpus, getOrMkList, mkGraph,
import Gargantext.Database.Schema.NodeNgram (NodeNgramPoly(..), insertNodeNgrams) import Gargantext.Database.Schema.NodeNgram (NodeNgramPoly(..), insertNodeNgrams)
import Gargantext.Database.Schema.NodeNgramsNgrams (NodeNgramsNgramsPoly(..), insertNodeNgramsNgramsNew) import Gargantext.Database.Schema.NodeNgramsNgrams (NodeNgramsNgramsPoly(..), insertNodeNgramsNgramsNew)
import Gargantext.Database.Schema.User (getUser, UserLight(..)) import Gargantext.Database.Schema.User (getUser, UserLight(..))
import Gargantext.Database.Types.Node (HyperdataDocument(..)) import Gargantext.Database.Types.Node (HyperdataDocument(..), NodeType(..), NodeId, UserId, ListId, CorpusId, RootId, MasterCorpusId, MasterUserId)
import Gargantext.Database.Types.Node (NodeType(..), NodeId)
import Gargantext.Database.Utils (Cmd) import Gargantext.Database.Utils (Cmd)
import Gargantext.Text.Terms (TermType(..)) import Gargantext.Text.Terms (TermType(..))
import Gargantext.Ext.IMT (toSchoolName) import Gargantext.Ext.IMT (toSchoolName)
...@@ -53,6 +52,7 @@ import Gargantext.Text.Parsers (parseDocs, FileFormat) ...@@ -53,6 +52,7 @@ import Gargantext.Text.Parsers (parseDocs, FileFormat)
import System.FilePath (FilePath) import System.FilePath (FilePath)
import qualified Data.Map as DM import qualified Data.Map as DM
flowCorpus :: HasNodeError err => FileFormat -> FilePath -> CorpusName -> Cmd err CorpusId flowCorpus :: HasNodeError err => FileFormat -> FilePath -> CorpusName -> Cmd err CorpusId
flowCorpus ff fp cName = do flowCorpus ff fp cName = do
hyperdataDocuments' <- map addUniqIdsDoc <$> liftIO (parseDocs ff fp) hyperdataDocuments' <- map addUniqIdsDoc <$> liftIO (parseDocs ff fp)
...@@ -67,10 +67,10 @@ flowInsert _nt hyperdataDocuments cName = do ...@@ -67,10 +67,10 @@ flowInsert _nt hyperdataDocuments cName = do
(masterUserId, _, masterCorpusId) <- subFlowCorpus userMaster corpusMasterName (masterUserId, _, masterCorpusId) <- subFlowCorpus userMaster corpusMasterName
ids <- insertDocuments masterUserId masterCorpusId NodeDocument hyperdataDocuments' ids <- insertDocuments masterUserId masterCorpusId NodeDocument hyperdataDocuments'
(userId, _, userCorpusId) <- subFlowCorpus userArbitrary cName (userId, _, userCorpusId) <- subFlowCorpus userArbitrary cName
_ <- add userCorpusId (map reId ids) _ <- add userCorpusId (map reId ids)
pure (ids, masterUserId, masterCorpusId, userId, userCorpusId) pure (ids, masterUserId, masterCorpusId, userId, userCorpusId)
...@@ -87,10 +87,10 @@ flowInsertAnnuaire name children = do ...@@ -87,10 +87,10 @@ flowInsertAnnuaire name children = do
(masterUserId, _, masterCorpusId) <- subFlowCorpus userMaster corpusMasterName (masterUserId, _, masterCorpusId) <- subFlowCorpus userMaster corpusMasterName
ids <- insertDocuments masterUserId masterCorpusId NodeContact children ids <- insertDocuments masterUserId masterCorpusId NodeContact children
(userId, _, userCorpusId) <- subFlowAnnuaire userArbitrary name (userId, _, userCorpusId) <- subFlowAnnuaire userArbitrary name
_ <- add userCorpusId (map reId ids) _ <- add userCorpusId (map reId ids)
printDebug "AnnuaireID" userCorpusId printDebug "AnnuaireID" userCorpusId
pure (ids, masterUserId, masterCorpusId, userId, userCorpusId) pure (ids, masterUserId, masterCorpusId, userId, userCorpusId)
...@@ -105,25 +105,25 @@ flowCorpus' NodeCorpus hyperdataDocuments (ids,masterUserId,masterCorpusId, user ...@@ -105,25 +105,25 @@ flowCorpus' NodeCorpus hyperdataDocuments (ids,masterUserId,masterCorpusId, user
-- List Ngrams Flow -- List Ngrams Flow
userListId <- flowListUser userId userCorpusId userListId <- flowListUser userId userCorpusId
printDebug "Working on User ListId : " userListId printDebug "Working on User ListId : " userListId
let documentsWithId = mergeData (toInserted ids) (toInsert hyperdataDocuments) let documentsWithId = mergeData (toInserted ids) (toInsert hyperdataDocuments)
-- printDebug "documentsWithId" documentsWithId -- printDebug "documentsWithId" documentsWithId
docsWithNgrams <- documentIdWithNgrams extractNgramsT documentsWithId docsWithNgrams <- documentIdWithNgrams extractNgramsT documentsWithId
-- printDebug "docsWithNgrams" docsWithNgrams -- printDebug "docsWithNgrams" docsWithNgrams
let maps = mapNodeIdNgrams docsWithNgrams let maps = mapNodeIdNgrams docsWithNgrams
-- printDebug "maps" (maps) -- printDebug "maps" (maps)
indexedNgrams <- indexNgrams maps indexedNgrams <- indexNgrams maps
-- printDebug "inserted ngrams" indexedNgrams -- printDebug "inserted ngrams" indexedNgrams
_ <- insertToNodeNgrams indexedNgrams _ <- insertToNodeNgrams indexedNgrams
listId2 <- flowList masterUserId masterCorpusId indexedNgrams listId2 <- flowList masterUserId masterCorpusId indexedNgrams
printDebug "Working on ListId : " listId2 printDebug "Working on ListId : " listId2
--} --}
-------------------------------------------------- --------------------------------------------------
_ <- mkDashboard userCorpusId userId _ <- mkDashboard userCorpusId userId
_ <- mkGraph userCorpusId userId _ <- mkGraph userCorpusId userId
-- Annuaire Flow -- Annuaire Flow
-- _ <- mkAnnuaire rootUserId userId -- _ <- mkAnnuaire rootUserId userId
...@@ -284,7 +284,7 @@ flowList uId cId ngs = do ...@@ -284,7 +284,7 @@ flowList uId cId ngs = do
pure lId pure lId
flowListUser :: HasNodeError err => UserId -> CorpusId -> Cmd err Int flowListUser :: HasNodeError err => UserId -> CorpusId -> Cmd err NodeId
flowListUser uId cId = getOrMkList cId uId flowListUser uId cId = getOrMkList cId uId
------------------------------------------------------------------------ ------------------------------------------------------------------------
......
...@@ -37,8 +37,8 @@ import Gargantext.Database.Schema.Ngrams -- (NgramsType(..)) ...@@ -37,8 +37,8 @@ import Gargantext.Database.Schema.Ngrams -- (NgramsType(..))
import Gargantext.Database.Node.Contact import Gargantext.Database.Node.Contact
import Gargantext.Database.Flow.Utils import Gargantext.Database.Flow.Utils
import Gargantext.Database.Utils (Cmd, runPGSQuery) import Gargantext.Database.Utils (Cmd, runPGSQuery)
import Gargantext.Database.Types.Node (AnnuaireId, CorpusId, ContactId)
import Gargantext.Database.Node.Children import Gargantext.Database.Node.Children
import Gargantext.Core.Types.Main
import Gargantext.Core.Types (NodeType(..)) import Gargantext.Core.Types (NodeType(..))
-- TODO mv this type in Types Main -- TODO mv this type in Types Main
......
...@@ -26,6 +26,7 @@ import Gargantext.Database.Schema.NodeNode ...@@ -26,6 +26,7 @@ import Gargantext.Database.Schema.NodeNode
import Gargantext.Database.Config (nodeTypeId) import Gargantext.Database.Config (nodeTypeId)
import Gargantext.Database.Queries.Filter import Gargantext.Database.Queries.Filter
import Gargantext.Database.Node.Contact (HyperdataContact) import Gargantext.Database.Node.Contact (HyperdataContact)
import Gargantext.Database.Schema.Node (pgNodeId)
import Control.Arrow (returnA) import Control.Arrow (returnA)
-- | TODO: use getChildren with Proxy ? -- | TODO: use getChildren with Proxy ?
...@@ -47,8 +48,8 @@ selectChildren parentId maybeNodeType = proc () -> do ...@@ -47,8 +48,8 @@ selectChildren parentId maybeNodeType = proc () -> do
let nodeType = maybe 0 nodeTypeId maybeNodeType let nodeType = maybe 0 nodeTypeId maybeNodeType
restrict -< typeName .== pgInt4 nodeType restrict -< typeName .== pgInt4 nodeType
restrict -< (.||) (parent_id .== (pgInt4 parentId)) restrict -< (.||) (parent_id .== (pgNodeId parentId))
( (.&&) (n1id .== pgInt4 parentId) ( (.&&) (n1id .== pgNodeId parentId)
(n2id .== nId)) (n2id .== nId))
returnA -< row returnA -< row
......
...@@ -28,9 +28,8 @@ import Data.Time (UTCTime) ...@@ -28,9 +28,8 @@ import Data.Time (UTCTime)
import Database.PostgreSQL.Simple.FromField (FromField, fromField) import Database.PostgreSQL.Simple.FromField (FromField, fromField)
import GHC.Generics (Generic) import GHC.Generics (Generic)
import Gargantext.Core.Utils.Prefix (unPrefix) import Gargantext.Core.Utils.Prefix (unPrefix)
import Gargantext.Core.Types.Main (AnnuaireId, UserId)
import Gargantext.Database.Schema.Node (NodeWrite, Name, node) import Gargantext.Database.Schema.Node (NodeWrite, Name, node)
import Gargantext.Database.Types.Node (Node,Hyperdata,NodeType(..)) import Gargantext.Database.Types.Node (Node,Hyperdata,NodeType(..), UserId, AnnuaireId)
import Gargantext.Database.Utils (fromField') import Gargantext.Database.Utils (fromField')
import Gargantext.Prelude import Gargantext.Prelude
import Opaleye (QueryRunnerColumnDefault, queryRunnerColumnDefault, PGJsonb, fieldQueryRunnerColumn) import Opaleye (QueryRunnerColumnDefault, queryRunnerColumnDefault, PGJsonb, fieldQueryRunnerColumn)
......
...@@ -40,7 +40,6 @@ import Gargantext.Prelude ...@@ -40,7 +40,6 @@ import Gargantext.Prelude
import GHC.Generics (Generic) import GHC.Generics (Generic)
--------------------------------------------------------------------------- ---------------------------------------------------------------------------
type ParentId = Int
add :: ParentId -> [NodeId] -> Cmd err [Only Int] add :: ParentId -> [NodeId] -> Cmd err [Only Int]
add pId ns = runPGSQuery queryAdd (Only $ Values fields inputData) add pId ns = runPGSQuery queryAdd (Only $ Values fields inputData)
......
...@@ -180,7 +180,7 @@ prepare uId pId nodeType = map (\h -> InputData tId uId pId (name h) (toJSON' h) ...@@ -180,7 +180,7 @@ prepare uId pId nodeType = map (\h -> InputData tId uId pId (name h) (toJSON' h)
-- | When documents are inserted -- | When documents are inserted
-- ReturnType after insertion -- ReturnType after insertion
data ReturnId = ReturnId { reInserted :: Bool -- ^ if the document is inserted (True: is new, False: is not new) data ReturnId = ReturnId { reInserted :: Bool -- ^ if the document is inserted (True: is new, False: is not new)
, reId :: Int -- ^ always return the id of the document (even new or not new) , reId :: NodeId -- ^ always return the id of the document (even new or not new)
-- this is the uniq id in the database -- this is the uniq id in the database
, reUniqId :: Text -- ^ Hash Id with concatenation of hash parameters , reUniqId :: Text -- ^ Hash Id with concatenation of hash parameters
} deriving (Show, Generic) } deriving (Show, Generic)
...@@ -190,9 +190,6 @@ instance FromRow ReturnId where ...@@ -190,9 +190,6 @@ instance FromRow ReturnId where
-- ** Insert Types -- ** Insert Types
type UserId = Int
type ParentId = Int
data InputData = InputData { inTypenameId :: NodeTypeId data InputData = InputData { inTypenameId :: NodeTypeId
, inUserId :: UserId , inUserId :: UserId
, inParentId :: ParentId , inParentId :: ParentId
......
...@@ -17,20 +17,18 @@ Portability : POSIX ...@@ -17,20 +17,18 @@ Portability : POSIX
module Gargantext.Database.Node.Update (Update(..), update) where module Gargantext.Database.Node.Update (Update(..), update) where
import Data.Text (Text)
import qualified Data.Text as DT import qualified Data.Text as DT
import Database.PostgreSQL.Simple import Database.PostgreSQL.Simple
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Database.Utils import Gargantext.Database.Utils
import Gargantext.Database.Types.Node (NodeId, ParentId)
import Gargantext.Database.Schema.Node (Name)
-- import Data.ByteString -- import Data.ByteString
--rename :: NodeId -> Text -> IO ByteString --rename :: NodeId -> Text -> IO ByteString
--rename nodeId name = formatPGSQuery "UPDATE nodes SET name=? where id=?" (name,nodeId) --rename nodeId name = formatPGSQuery "UPDATE nodes SET name=? where id=?" (name,nodeId)
------------------------------------------------------------------------ ------------------------------------------------------------------------
type NodeId = Int
type Name = Text
type ParentId = Int
data Update = Rename NodeId Name data Update = Rename NodeId Name
| Move NodeId ParentId | Move NodeId ParentId
......
...@@ -221,8 +221,8 @@ getNgramsTableDb nt ngrt ntp@(NgramsTableParam listIdUser _) limit_ offset_ = do ...@@ -221,8 +221,8 @@ getNgramsTableDb nt ngrt ntp@(NgramsTableParam listIdUser _) limit_ offset_ = do
data NgramsTableParam = data NgramsTableParam =
NgramsTableParam { _nt_listId :: Int NgramsTableParam { _nt_listId :: NodeId
, _nt_corpusId :: Int , _nt_corpusId :: NodeId
} }
type NgramsTableParamUser = NgramsTableParam type NgramsTableParamUser = NgramsTableParam
...@@ -289,8 +289,8 @@ querySelectTableNgrams = [sql| ...@@ -289,8 +289,8 @@ querySelectTableNgrams = [sql|
|] |]
type ListIdUser = Int type ListIdUser = NodeId
type ListIdMaster = Int type ListIdMaster = NodeId
type MapToChildren = Map Text (Set Text) type MapToChildren = Map Text (Set Text)
type MapToParent = Map Text Text type MapToParent = Map Text Text
......
This diff is collapsed.
...@@ -36,9 +36,11 @@ import Control.Monad (void) ...@@ -36,9 +36,11 @@ import Control.Monad (void)
import Data.Profunctor.Product.TH (makeAdaptorAndInstance) import Data.Profunctor.Product.TH (makeAdaptorAndInstance)
import Database.PostgreSQL.Simple.Types (Values(..), QualifiedIdentifier(..)) import Database.PostgreSQL.Simple.Types (Values(..), QualifiedIdentifier(..))
import Database.PostgreSQL.Simple.SqlQQ (sql) import Database.PostgreSQL.Simple.SqlQQ (sql)
import Gargantext.Core.Types.Main (ListId, ListTypeId) import Gargantext.Core.Types.Main (ListTypeId)
import Gargantext.Database.Utils (mkCmd, Cmd, execPGSQuery) import Gargantext.Database.Utils (mkCmd, Cmd, execPGSQuery)
import Gargantext.Database.Schema.NodeNgramsNgrams import Gargantext.Database.Types.Node (NodeId, ListId)
import Gargantext.Database.Schema.Node (pgNodeId)
import Gargantext.Database.Schema.NodeNgramsNgrams (NgramsChild, NgramsParent, ngramsGroup, Action(..))
import Gargantext.Prelude import Gargantext.Prelude
import Opaleye import Opaleye
import qualified Database.PostgreSQL.Simple as PGS (Only(..)) import qualified Database.PostgreSQL.Simple as PGS (Only(..))
...@@ -77,7 +79,7 @@ type NodeNgramReadNull = ...@@ -77,7 +79,7 @@ type NodeNgramReadNull =
(Column (Nullable PGInt4 )) (Column (Nullable PGInt4 ))
type NodeNgram = type NodeNgram =
NodeNgramPoly (Maybe Int) Int Int Double Int NodeNgramPoly (Maybe NodeId) NodeId Int Double Int
$(makeAdaptorAndInstance "pNodeNgram" ''NodeNgramPoly) $(makeAdaptorAndInstance "pNodeNgram" ''NodeNgramPoly)
$(makeLensesWith abbreviatedFields ''NodeNgramPoly) $(makeLensesWith abbreviatedFields ''NodeNgramPoly)
...@@ -100,7 +102,7 @@ queryNodeNgramTable = queryTable nodeNgramTable ...@@ -100,7 +102,7 @@ queryNodeNgramTable = queryTable nodeNgramTable
insertNodeNgrams :: [NodeNgram] -> Cmd err Int insertNodeNgrams :: [NodeNgram] -> Cmd err Int
insertNodeNgrams = insertNodeNgramW insertNodeNgrams = insertNodeNgramW
. map (\(NodeNgram _ n g w t) -> . map (\(NodeNgram _ n g w t) ->
NodeNgram Nothing (pgInt4 n) (pgInt4 g) NodeNgram Nothing (pgNodeId n) (pgInt4 g)
(pgDouble w) (pgInt4 t) (pgDouble w) (pgInt4 t)
) )
......
...@@ -42,7 +42,8 @@ import Data.Profunctor.Product.TH (makeAdaptorAndInstance) ...@@ -42,7 +42,8 @@ import Data.Profunctor.Product.TH (makeAdaptorAndInstance)
import Database.PostgreSQL.Simple.SqlQQ (sql) import Database.PostgreSQL.Simple.SqlQQ (sql)
import Database.PostgreSQL.Simple.Types (Values(..), QualifiedIdentifier(..)) import Database.PostgreSQL.Simple.Types (Values(..), QualifiedIdentifier(..))
import Gargantext.Database.Utils (Cmd, runOpaQuery, execPGSQuery, connection) import Gargantext.Database.Utils (Cmd, runOpaQuery, execPGSQuery, connection)
import Gargantext.Core.Types.Main (ListId) import Gargantext.Database.Types.Node (ListId)
import Gargantext.Database.Schema.Node (pgNodeId)
import Gargantext.Prelude import Gargantext.Prelude
import Opaleye import Opaleye
import qualified Database.PostgreSQL.Simple as PGS import qualified Database.PostgreSQL.Simple as PGS
...@@ -67,7 +68,7 @@ type NodeNgramsNgramsRead = ...@@ -67,7 +68,7 @@ type NodeNgramsNgramsRead =
(Column PGFloat8) (Column PGFloat8)
type NodeNgramsNgrams = type NodeNgramsNgrams =
NodeNgramsNgramsPoly Int NodeNgramsNgramsPoly ListId
Int Int
Int Int
(Maybe Double) (Maybe Double)
...@@ -108,7 +109,7 @@ instance QueryRunnerColumnDefault PGFloat8 (Maybe Double) where ...@@ -108,7 +109,7 @@ instance QueryRunnerColumnDefault PGFloat8 (Maybe Double) where
insertNodeNgramsNgramsNew :: [NodeNgramsNgrams] -> Cmd err Int insertNodeNgramsNgramsNew :: [NodeNgramsNgrams] -> Cmd err Int
insertNodeNgramsNgramsNew = insertNodeNgramsNgramsW insertNodeNgramsNgramsNew = insertNodeNgramsNgramsW
. map (\(NodeNgramsNgrams n ng1 ng2 maybeWeight) -> . map (\(NodeNgramsNgrams n ng1 ng2 maybeWeight) ->
NodeNgramsNgrams (pgInt4 n ) NodeNgramsNgrams (pgNodeId n )
(pgInt4 ng1) (pgInt4 ng1)
(pgInt4 ng2) (pgInt4 ng2)
(pgDouble <$> maybeWeight) (pgDouble <$> maybeWeight)
......
...@@ -32,7 +32,7 @@ import Control.Lens.TH (makeLensesWith, abbreviatedFields) ...@@ -32,7 +32,7 @@ import Control.Lens.TH (makeLensesWith, abbreviatedFields)
import Data.Maybe (Maybe) import Data.Maybe (Maybe)
import Data.Profunctor.Product.TH (makeAdaptorAndInstance) import Data.Profunctor.Product.TH (makeAdaptorAndInstance)
import Gargantext.Database.Utils import Gargantext.Database.Utils
import Gargantext.Core.Types.Main (CorpusId, DocId) import Gargantext.Database.Types.Node (CorpusId, DocId)
import Gargantext.Prelude import Gargantext.Prelude
import Opaleye import Opaleye
......
...@@ -64,7 +64,7 @@ searchInCorpus cId q o l order = runOpaQuery (filterWith o l order $ queryInCorp ...@@ -64,7 +64,7 @@ searchInCorpus cId q o l order = runOpaQuery (filterWith o l order $ queryInCorp
queryInCorpus :: CorpusId -> Text -> O.Query FacetDocRead queryInCorpus :: CorpusId -> Text -> O.Query FacetDocRead
queryInCorpus cId q = proc () -> do queryInCorpus cId q = proc () -> do
(n, nn) <- joinInCorpus -< () (n, nn) <- joinInCorpus -< ()
restrict -< ( nodeNode_node1_id nn) .== (toNullable $ pgInt4 cId) restrict -< ( nodeNode_node1_id nn) .== (toNullable $ pgNodeId cId)
restrict -< (_ns_search n) @@ (pgTSQuery (unpack q)) restrict -< (_ns_search n) @@ (pgTSQuery (unpack q))
restrict -< (_ns_typename n) .== (pgInt4 $ nodeTypeId NodeDocument) restrict -< (_ns_typename n) .== (pgInt4 $ nodeTypeId NodeDocument)
returnA -< FacetDoc (_ns_id n) (_ns_date n) (_ns_name n) (_ns_hyperdata n) (pgBool True) (pgInt4 1) returnA -< FacetDoc (_ns_id n) (_ns_date n) (_ns_name n) (_ns_hyperdata n) (pgBool True) (pgInt4 1)
...@@ -103,7 +103,7 @@ queryInCorpusWithContacts cId q _ _ _ = proc () -> do ...@@ -103,7 +103,7 @@ queryInCorpusWithContacts cId q _ _ _ = proc () -> do
(docs, (corpusDoc, (docNgrams, (ngrams', (_, contacts))))) <- joinInCorpusWithContacts -< () (docs, (corpusDoc, (docNgrams, (ngrams', (_, contacts))))) <- joinInCorpusWithContacts -< ()
restrict -< (_ns_search docs) @@ (pgTSQuery $ unpack q ) restrict -< (_ns_search docs) @@ (pgTSQuery $ unpack q )
restrict -< (_ns_typename docs) .== (pgInt4 $ nodeTypeId NodeDocument) restrict -< (_ns_typename docs) .== (pgInt4 $ nodeTypeId NodeDocument)
restrict -< (nodeNode_node1_id corpusDoc) .== (toNullable $ pgInt4 cId) restrict -< (nodeNode_node1_id corpusDoc) .== (toNullable $ pgNodeId cId)
restrict -< (nodeNgram_type docNgrams) .== (toNullable $ pgInt4 $ ngramsTypeId Authors) restrict -< (nodeNgram_type docNgrams) .== (toNullable $ pgInt4 $ ngramsTypeId Authors)
restrict -< (_node_typename contacts) .== (toNullable $ pgInt4 $ nodeTypeId NodeContact) restrict -< (_node_typename contacts) .== (toNullable $ pgInt4 $ nodeTypeId NodeContact)
-- let contact_id = ifThenElse (isNull $ _node_id contacts) (toNullable $ pgInt4 0) (_node_id contacts) -- let contact_id = ifThenElse (isNull $ _node_id contacts) (toNullable $ pgInt4 0) (_node_id contacts)
......
...@@ -27,6 +27,7 @@ import Database.PostgreSQL.Simple.SqlQQ ...@@ -27,6 +27,7 @@ import Database.PostgreSQL.Simple.SqlQQ
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Core.Types.Main (NodeTree(..), Tree(..)) import Gargantext.Core.Types.Main (NodeTree(..), Tree(..))
import Gargantext.Database.Types.Node (NodeId)
import Gargantext.Database.Config (fromNodeTypeId) import Gargantext.Database.Config (fromNodeTypeId)
import Gargantext.Database.Utils (Cmd, runPGSQuery) import Gargantext.Database.Utils (Cmd, runPGSQuery)
------------------------------------------------------------------------ ------------------------------------------------------------------------
...@@ -48,8 +49,8 @@ treeError te = throwError $ _TreeError # te ...@@ -48,8 +49,8 @@ treeError te = throwError $ _TreeError # te
treeDB :: HasTreeError err => RootId -> Cmd err (Tree NodeTree) treeDB :: HasTreeError err => RootId -> Cmd err (Tree NodeTree)
treeDB r = toTree =<< (toTreeParent <$> dbTree r) treeDB r = toTree =<< (toTreeParent <$> dbTree r)
type RootId = Int type RootId = NodeId
type ParentId = Int type ParentId = NodeId
------------------------------------------------------------------------ ------------------------------------------------------------------------
toTree :: (MonadError e m, HasTreeError e) toTree :: (MonadError e m, HasTreeError e)
=> Map (Maybe ParentId) [DbTreeNode] -> m (Tree NodeTree) => Map (Maybe ParentId) [DbTreeNode] -> m (Tree NodeTree)
...@@ -74,9 +75,9 @@ toNodeTree (DbTreeNode nId tId _ n) = NodeTree n nodeType nId ...@@ -74,9 +75,9 @@ toNodeTree (DbTreeNode nId tId _ n) = NodeTree n nodeType nId
toTreeParent :: [DbTreeNode] -> Map (Maybe ParentId) [DbTreeNode] toTreeParent :: [DbTreeNode] -> Map (Maybe ParentId) [DbTreeNode]
toTreeParent = fromListWith (<>) . map (\n -> (dt_parentId n, [n])) toTreeParent = fromListWith (<>) . map (\n -> (dt_parentId n, [n]))
------------------------------------------------------------------------ ------------------------------------------------------------------------
data DbTreeNode = DbTreeNode { dt_nodeId :: Int data DbTreeNode = DbTreeNode { dt_nodeId :: NodeId
, dt_typeId :: Int , dt_typeId :: Int
, dt_parentId :: Maybe Int , dt_parentId :: Maybe NodeId
, dt_name :: Text , dt_name :: Text
} deriving (Show) } deriving (Show)
......
...@@ -18,6 +18,7 @@ Portability : POSIX ...@@ -18,6 +18,7 @@ Portability : POSIX
{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
-- {-# LANGUAGE DuplicateRecordFields #-} -- {-# LANGUAGE DuplicateRecordFields #-}
module Gargantext.Database.Types.Node module Gargantext.Database.Types.Node
...@@ -48,6 +49,7 @@ import Text.Read (read) ...@@ -48,6 +49,7 @@ import Text.Read (read)
import Text.Show (Show()) import Text.Show (Show())
import Database.PostgreSQL.Simple.ToField (ToField, toField, toJSONField) import Database.PostgreSQL.Simple.ToField (ToField, toField, toJSONField)
import Database.PostgreSQL.Simple.FromField (FromField, fromField)
import Servant import Servant
import Test.QuickCheck.Arbitrary import Test.QuickCheck.Arbitrary
...@@ -55,8 +57,45 @@ import Test.QuickCheck (elements) ...@@ -55,8 +57,45 @@ import Test.QuickCheck (elements)
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Core.Utils.Prefix (unPrefix) import Gargantext.Core.Utils.Prefix (unPrefix)
import Gargantext.Database.Utils
------------------------------------------------------------------------ ------------------------------------------------------------------------
type NodeId = Int newtype NodeId = NodeId Int
deriving (Show, Read, Generic, Num, Eq, Ord, Enum)
instance ToField NodeId where
toField (NodeId n) = toField n
instance FromField NodeId where
fromField = fromField'
instance ToJSON NodeId
instance FromJSON NodeId
instance ToSchema NodeId
instance FromHttpApiData NodeId where
parseUrlPiece n = pure $ NodeId $ (read . cs) n
instance ToParamSchema NodeId
instance Arbitrary NodeId where
arbitrary = NodeId <$> arbitrary
type ParentId = NodeId
type GraphId = NodeId
type CorpusId = NodeId
type ListId = NodeId
type DocumentId = NodeId
type DocId = DocumentId -- todo: remove this
type RootId = NodeId
type MasterCorpusId = NodeId
type AnnuaireId = NodeId
type ContactId = NodeId
type UserId = Int
type MasterUserId = UserId
id2int :: NodeId -> Int
id2int (NodeId n) = n
type UTCTime' = UTCTime type UTCTime' = UTCTime
...@@ -328,12 +367,10 @@ instance Hyperdata HyperdataNotebook ...@@ -328,12 +367,10 @@ instance Hyperdata HyperdataNotebook
-- | NodePoly indicates that Node has a Polymorphism Type -- | NodePoly indicates that Node has a Polymorphism Type
type Node json = NodePoly NodeId NodeTypeId NodeUserId (Maybe NodeParentId) NodeName UTCTime json type Node json = NodePoly NodeId NodeTypeId UserId (Maybe ParentId) NodeName UTCTime json
-- type Node json = NodePoly NodeId NodeTypeId UserId ParentId NodeName UTCTime json -- type Node json = NodePoly NodeId NodeTypeId UserId ParentId NodeName UTCTime json
type NodeTypeId = Int type NodeTypeId = Int
type NodeParentId = Int
type NodeUserId = Int
type NodeName = Text type NodeName = Text
type TSVector = Text type TSVector = Text
...@@ -375,8 +412,8 @@ allNodeTypes = [minBound ..] ...@@ -375,8 +412,8 @@ allNodeTypes = [minBound ..]
instance FromJSON NodeType instance FromJSON NodeType
instance ToJSON NodeType instance ToJSON NodeType
instance FromHttpApiData NodeType instance FromHttpApiData NodeType
where where
parseUrlPiece = Right . read . unpack parseUrlPiece = Right . read . unpack
instance ToParamSchema NodeType instance ToParamSchema NodeType
...@@ -416,16 +453,16 @@ data NodePolySearch id typename userId ...@@ -416,16 +453,16 @@ data NodePolySearch id typename userId
$(deriveJSON (unPrefix "_ns_") ''NodePolySearch) $(deriveJSON (unPrefix "_ns_") ''NodePolySearch)
$(makeLenses ''NodePolySearch) $(makeLenses ''NodePolySearch)
type NodeSearch json = NodePolySearch NodeId NodeTypeId NodeUserId (Maybe NodeParentId) NodeName UTCTime json (Maybe TSVector) type NodeSearch json = NodePolySearch NodeId NodeTypeId UserId (Maybe ParentId) NodeName UTCTime json (Maybe TSVector)
------------------------------------------------------------------------ ------------------------------------------------------------------------
instance (Arbitrary hyperdata instance (Arbitrary hyperdata
,Arbitrary nodeId ,Arbitrary nodeId
,Arbitrary nodeTypeId ,Arbitrary nodeTypeId
,Arbitrary nodeUserId ,Arbitrary userId
,Arbitrary nodeParentId ,Arbitrary nodeParentId
) => Arbitrary (NodePoly nodeId nodeTypeId nodeUserId nodeParentId ) => Arbitrary (NodePoly nodeId nodeTypeId userId nodeParentId
NodeName UTCTime hyperdata) where NodeName UTCTime hyperdata) where
--arbitrary = Node 1 1 (Just 1) 1 "name" (jour 2018 01 01) (arbitrary) (Just "") --arbitrary = Node 1 1 (Just 1) 1 "name" (jour 2018 01 01) (arbitrary) (Just "")
arbitrary = Node <$> arbitrary <*> arbitrary <*> arbitrary arbitrary = Node <$> arbitrary <*> arbitrary <*> arbitrary
...@@ -435,9 +472,9 @@ instance (Arbitrary hyperdata ...@@ -435,9 +472,9 @@ instance (Arbitrary hyperdata
instance (Arbitrary hyperdata instance (Arbitrary hyperdata
,Arbitrary nodeId ,Arbitrary nodeId
,Arbitrary nodeTypeId ,Arbitrary nodeTypeId
,Arbitrary nodeUserId ,Arbitrary userId
,Arbitrary nodeParentId ,Arbitrary nodeParentId
) => Arbitrary (NodePolySearch nodeId nodeTypeId nodeUserId nodeParentId ) => Arbitrary (NodePolySearch nodeId nodeTypeId userId nodeParentId
NodeName UTCTime hyperdata (Maybe TSVector)) where NodeName UTCTime hyperdata (Maybe TSVector)) where
--arbitrary = Node 1 1 (Just 1) 1 "name" (jour 2018 01 01) (arbitrary) (Just "") --arbitrary = Node 1 1 (Just 1) 1 "name" (jour 2018 01 01) (arbitrary) (Just "")
arbitrary = NodeSearch <$> arbitrary <*> arbitrary <*> arbitrary arbitrary = NodeSearch <$> arbitrary <*> arbitrary <*> arbitrary
...@@ -484,30 +521,30 @@ instance ToSchema HyperdataAny where ...@@ -484,30 +521,30 @@ instance ToSchema HyperdataAny where
instance ToSchema hyperdata => instance ToSchema hyperdata =>
ToSchema (NodePoly NodeId NodeTypeId ToSchema (NodePoly NodeId NodeTypeId
(Maybe NodeUserId) (Maybe UserId)
NodeParentId NodeName ParentId NodeName
UTCTime hyperdata UTCTime hyperdata
) )
instance ToSchema hyperdata => instance ToSchema hyperdata =>
ToSchema (NodePoly NodeId NodeTypeId ToSchema (NodePoly NodeId NodeTypeId
NodeUserId UserId
(Maybe NodeParentId) NodeName (Maybe ParentId) NodeName
UTCTime hyperdata UTCTime hyperdata
) )
instance ToSchema hyperdata => instance ToSchema hyperdata =>
ToSchema (NodePolySearch NodeId NodeTypeId ToSchema (NodePolySearch NodeId NodeTypeId
(Maybe NodeUserId) (Maybe UserId)
NodeParentId NodeName ParentId NodeName
UTCTime hyperdata (Maybe TSVector) UTCTime hyperdata (Maybe TSVector)
) )
instance ToSchema hyperdata => instance ToSchema hyperdata =>
ToSchema (NodePolySearch NodeId NodeTypeId ToSchema (NodePolySearch NodeId NodeTypeId
NodeUserId UserId
(Maybe NodeParentId) NodeName (Maybe ParentId) NodeName
UTCTime hyperdata (Maybe TSVector) UTCTime hyperdata (Maybe TSVector)
) )
......
...@@ -129,4 +129,3 @@ fromField' field mb = do ...@@ -129,4 +129,3 @@ fromField' field mb = do
printSqlOpa :: Default Unpackspec a a => Query a -> IO () printSqlOpa :: Default Unpackspec a a => Query a -> IO ()
printSqlOpa = putStrLn . maybe "Empty query" identity . showSqlForPostgres printSqlOpa = putStrLn . maybe "Empty query" identity . showSqlForPostgres
...@@ -38,6 +38,7 @@ import Data.Swagger ...@@ -38,6 +38,7 @@ import Data.Swagger
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Core.Types (Label) import Gargantext.Core.Types (Label)
import Gargantext.Core.Utils.Prefix (unPrefix) import Gargantext.Core.Utils.Prefix (unPrefix)
import Gargantext.Database.Types.Node (NodeId)
import Data.Graph.Clustering.Louvain.CplusPlus (LouvainNode(..)) import Data.Graph.Clustering.Louvain.CplusPlus (LouvainNode(..))
...@@ -98,7 +99,7 @@ instance ToSchema LegendField where ...@@ -98,7 +99,7 @@ instance ToSchema LegendField where
makeLenses ''LegendField makeLenses ''LegendField
-- --
data GraphMetadata = GraphMetadata { _gm_title :: Text -- title of the graph data GraphMetadata = GraphMetadata { _gm_title :: Text -- title of the graph
, _gm_corpusId :: [Int] -- we can map with different corpus , _gm_corpusId :: [NodeId] -- we can map with different corpus
, _gm_legend :: [LegendField] -- legend of the Graph , _gm_legend :: [LegendField] -- legend of the Graph
} }
deriving (Show, Generic) deriving (Show, Generic)
...@@ -140,24 +141,23 @@ data AttributesV3 = AttributesV3 { cl :: Int } ...@@ -140,24 +141,23 @@ data AttributesV3 = AttributesV3 { cl :: Int }
$(deriveJSON (unPrefix "") ''AttributesV3) $(deriveJSON (unPrefix "") ''AttributesV3)
data NodeV3 = NodeV3 { no_id :: Int data NodeV3 = NodeV3 { no_id :: Int
, no_at :: AttributesV3 , no_at :: AttributesV3
, no_s :: Int , no_s :: Int
, no_lb :: Text , no_lb :: Text
} }
deriving (Show, Generic) deriving (Show, Generic)
$(deriveJSON (unPrefix "no_") ''NodeV3) $(deriveJSON (unPrefix "no_") ''NodeV3)
data EdgeV3 = EdgeV3 { eo_s :: Int data EdgeV3 = EdgeV3 { eo_s :: Int
, eo_t :: Int , eo_t :: Int
, eo_w :: Text , eo_w :: Text
} }
deriving (Show, Generic) deriving (Show, Generic)
$(deriveJSON (unPrefix "eo_") ''EdgeV3) $(deriveJSON (unPrefix "eo_") ''EdgeV3)
data GraphV3 = GraphV3 { data GraphV3 = GraphV3 { go_links :: [EdgeV3]
go_links :: [EdgeV3] , go_nodes :: [NodeV3]
, go_nodes :: [NodeV3] }
}
deriving (Show, Generic) deriving (Show, Generic)
$(deriveJSON (unPrefix "go_") ''GraphV3) $(deriveJSON (unPrefix "go_") ''GraphV3)
......
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