[graphql] context ngrams works now

parent eab87bd7
......@@ -21,6 +21,8 @@ import Effect.Aff (launchAff_)
import Gargantext.Components.Category (CategoryQuery(..), putCategories)
import Gargantext.Components.Category.Types (Category(..), decodeCategory, favCategory)
import Gargantext.Components.DocsTable.Types (showSource)
import Gargantext.Components.GraphQL.Context as GQLCTX
import Gargantext.Components.GraphQL.Endpoints as GQLE
import Gargantext.Components.Search (Contact(..), Document(..), HyperdataRowContact(..), HyperdataRowDocument(..), SearchQuery, SearchResult(..), SearchResultTypes(..))
import Gargantext.Components.Table as T
import Gargantext.Components.Table.Types as T
......@@ -91,6 +93,21 @@ derive instance Generic DocumentsView _
instance Eq DocumentsView where eq = genericEq
instance Show DocumentsView where show = genericShow
gqlContextToDocumentsView :: GQLCTX.Context -> DocumentsView
gqlContextToDocumentsView ctx@{ c_hyperdata: h } =
DocumentsView { id: ctx.c_id
, date: ctx.c_date
, title: ctx.c_name
, source: showSource (_.hrd_source <$> h)
, score: fromMaybe 0 ctx.c_score
, authors: fromMaybe "Authors" (_.hrd_authors <$> h)
, category: decodeCategory $ fromMaybe 0 ctx.c_category
, pairs: []
, delete: false
, publication_year: _.hrd_publication_year <$> h
, publication_month: _.hrd_publication_month <$> h
, publication_day: _.hrd_publication_day <$> h }
----------------------------------------------------------------------
newtype ContactsView =
ContactsView
......@@ -218,7 +235,6 @@ loadPage { session, nodeId, listId, query, params: {limit, offset, orderBy } } =
convOrderBy (T.ASC (T.ColumnName "Source")) = SourceAsc
convOrderBy (T.DESC (T.ColumnName "Source")) = SourceDesc
convOrderBy _ = DateAsc -- TODO
p = Search { listId, offset, limit, orderBy: convOrderBy <$> orderBy } (Just nodeId)
--SearchResult {result} <- post session p $ SearchQuery {query: concat query, expected:searchType}
......@@ -233,6 +249,28 @@ loadPage { session, nodeId, listId, query, params: {limit, offset, orderBy } } =
SearchResultContact {contacts} -> Contacts {contacts: contact2view <$> Seq.fromFoldable contacts}
errMessage -> Docs {docs: Seq.fromFoldable [err2view errMessage]} -- TODO better error view
type PageGQLParams =
( corpusId :: Int
, params :: T.Params
, ngramsTerms :: Array String
, session :: Session )
initialPageGQL :: { corpusId :: Int, ngramsTerms :: Array String, session :: Session }
-> Record PageGQLParams
initialPageGQL { corpusId, ngramsTerms, session } =
{ corpusId, ngramsTerms, params: T.initialParams, session }
loadPageGQL :: Record PageGQLParams -> AffRESTError Rows
loadPageGQL { corpusId
, params: { limit, offset, orderBy }
, ngramsTerms
, session } = do
eResult <- GQLE.getContextsForNgrams session corpusId ngramsTerms
pure $ (\res -> Docs { docs: gqlContextToDocumentsView <$> Seq.fromFoldable res }) <$> eResult
doc2view :: Document -> DocumentsView
doc2view ( Document { id
, created: date
......
......@@ -11,7 +11,6 @@ import Data.Maybe (Maybe(..), fromJust)
import Data.Nullable (null, Nullable)
import Data.Sequence as Seq
import Data.Set as Set
import Data.Traversable (traverse_)
import Data.Tuple (Tuple(..))
import Effect (Effect)
import Gargantext.Components.App.Store as AppStore
......@@ -29,7 +28,6 @@ import Gargantext.Components.GraphExplorer.Utils as GEU
import Gargantext.Config (defaultFrontends)
import Gargantext.Data.Louvain as DLouvain
import Gargantext.Hooks.Sigmax.ForceAtlas2 as ForceAtlas
import Gargantext.Hooks.Sigmax.Graphology as Graphology
import Gargantext.Hooks.Sigmax.Louvain as Louvain
import Gargantext.Hooks.Sigmax.Noverlap as Noverlap
import Gargantext.Hooks.Sigmax as Sigmax
......
......@@ -4,7 +4,8 @@ module Gargantext.Components.GraphExplorer.Sidebar.DocList
import Gargantext.Prelude
import Data.Array (concat, head)
import Data.Array (catMaybes, concat, head)
import Data.Array as A
import Data.Foldable (intercalate)
import Data.Map as Map
import Data.Maybe (Maybe(..))
......@@ -14,7 +15,7 @@ import Data.Tuple.Nested ((/\))
import Effect (Effect)
import Gargantext.Components.Bootstrap as B
import Gargantext.Components.Bootstrap.Types (Variant(..))
import Gargantext.Components.FacetsTable (DocumentsView(..), Rows(..), initialPagePath, loadPage, publicationDate)
import Gargantext.Components.FacetsTable (DocumentsView(..), Rows(..), initialPagePath, initialPageGQL, loadPage, loadPageGQL, publicationDate)
import Gargantext.Components.GraphExplorer.Store as GraphStore
import Gargantext.Components.GraphExplorer.Types (CorpusId, DocId, GraphSideDoc(..), ListId)
import Gargantext.Components.GraphExplorer.Types as GET
......@@ -61,26 +62,17 @@ docListWrapperCpt = here.component "docListWrapper" cpt where
graph' <- R2.useLive' graph
selectedNodeIds' <- R2.useLive' selectedNodeIds
query' /\ query <- R2.useBox' Nothing
selectedNgramsTerms <- T.useBox []
-- | Helpers
-- |
let
nodesMap = SigmaxT.nodesGraphMap graph'
toSearchQuery ids = SearchQuery
{ expected: SearchDoc
, query: concat $ toQuery <$> Set.toUnfoldable ids
}
toQuery id = case Map.lookup id nodesMap of
Nothing -> []
Just n -> words n.label
-- | Hooks
-- |
R.useEffect1' selectedNodeIds' $ do
T.write_ (Just $ toSearchQuery selectedNodeIds') query
T.write_ (catMaybes $ (\id -> _.label <$> Map.lookup id nodesMap) <$> Set.toUnfoldable selectedNodeIds') selectedNgramsTerms
-- | Render
-- |
......@@ -88,16 +80,16 @@ docListWrapperCpt = here.component "docListWrapper" cpt where
R.fragment
[
case (head metaData.corpusId) /\ query' of
case (head metaData.corpusId) /\ (Set.isEmpty selectedNodeIds') of
(Just corpusId) /\ (Just q') ->
(Just corpusId) /\ false ->
docList
{ query: q'
, session
, corpusId
{ corpusId
, frontends: defaultFrontends
, listId: metaData.list.listId
, selectedNgramsTerms
, session
, showDoc
, frontends: defaultFrontends
}
_ /\ _ ->
......@@ -112,12 +104,12 @@ docListWrapperCpt = here.component "docListWrapper" cpt where
-------------------------------------------------------------------
type ListProps =
( query :: SearchQuery
, corpusId :: CorpusId
( corpusId :: CorpusId
, frontends :: Frontends
, listId :: ListId
, selectedNgramsTerms :: T.Box (Array SigmaxT.Label)
, session :: Session
, showDoc :: T.Box (Maybe GraphSideDoc)
, frontends :: Frontends
)
docList :: R2.Leaf ListProps
......@@ -134,18 +126,25 @@ docListCpt = here.component "docList" cpt where
_ -> pure unit
-- | Component
-- |
cpt { query
, session
, corpusId: nodeId
cpt { corpusId: nodeId
, frontends
, listId
, selectedNgramsTerms
, session
, showDoc
, frontends
} _ = do
-- | States
-- |
-- path' /\ path
-- <- R2.useBox' $ initialPagePath { nodeId, listId, query, session }
selectedNgramsTerms' <- T.useLive T.unequal selectedNgramsTerms
path' /\ path
<- R2.useBox' $ initialPagePath { nodeId, listId, query, session }
<- R2.useBox' $ initialPageGQL { corpusId: nodeId
, ngramsTerms: A.fromFoldable selectedNgramsTerms'
, session }
state' /\ state <-
R2.useBox' Nothing
......@@ -161,20 +160,26 @@ docListCpt = here.component "docList" cpt where
useLoaderEffect
{ errorHandler
, state
, loader: loadPage
, loader: loadPageGQL
, path: path'
, state
}
-- | Effects
-- |
-- (on query change, reload fetched docs)
useUpdateEffect1' query $
flip T.write_ path $ initialPagePath { nodeId, listId, query, session }
--useUpdateEffect1' query $
--flip T.write_ path $ initialPagePath { nodeId, listId, query, session }
useUpdateEffect1' selectedNgramsTerms' $
flip T.write_ path $ initialPageGQL { corpusId: nodeId
, ngramsTerms: A.fromFoldable selectedNgramsTerms'
, session }
-- (on fetch success, extract existing docs)
useUpdateEffect1' state' case state' of
useUpdateEffect1' state' do
here.log2 "[docList] state'" state'
case state' of
Nothing -> T.write_ (Just Seq.empty) rows
Just r -> case r of
Docs { docs } -> T.write_ (Just docs) rows
......
......@@ -74,7 +74,7 @@ queryGql session name q = do
type Schema
= { annuaire_contacts :: { contact_id :: Int } ==> Array AnnuaireContact
, contexts :: { context_id :: Int, node_id :: Int } ==> Array GQLCTX.NodeContext
, contexts_for_ngrams :: { corpus_id :: Int, ngrams_ids :: Array Int } ==> Array GQLCTX.Context
, contexts_for_ngrams :: { corpus_id :: Int, ngrams_terms :: Array String } ==> Array GQLCTX.Context
, imt_schools :: {} ==> Array GQLIMT.School
, node_parent :: { node_id :: Int, parent_type :: String } ==> Array Node -- TODO: parent_type :: NodeType
, nodes :: { node_id :: Int } ==> Array Node
......
......@@ -8,14 +8,17 @@ module Gargantext.Components.GraphQL.Context
, nodeContextQuery
, NodeContextCategoryM
, contextsForNgramsQuery
, NgramsTerms(..)
) where
import Gargantext.Prelude
import Data.Argonaut (class EncodeJson, encodeJson)
import Data.Lens (Lens', lens)
import Data.Maybe (Maybe(..), fromMaybe)
import GraphQL.Client.Args (Args, NotNull, (=>>))
import GraphQL.Client.Args (Args, NotNull, (=>>), class ArgGql)
import GraphQL.Client.Variable (Var(..))
import GraphQL.Client.Variables.TypeName (class VarTypeName, varTypeName)
import Gargantext.Utils.GraphQL as GGQL
import Type.Proxy (Proxy(..))
......@@ -25,9 +28,12 @@ type Context_
= ( c_id :: Int
, c_name :: String
, c_typename :: Int
, c_hash_id :: String
, c_date :: String
, c_hash_id :: Maybe String
, c_user_id :: Int
, c_parent_id :: Int
, c_parent_id :: Maybe Int
, c_category :: Maybe Int
, c_score :: Maybe Int -- TODO: Maybe Double
, c_hyperdata :: Maybe Hyperdata )
type Context = Record Context_
......@@ -86,13 +92,16 @@ nodeContextQuery
type ContextsForNgramsQuery
= { contexts_for_ngrams :: Args
{ corpus_id :: Var "corpus_id" Int
, ngrams_ids :: Var "ngrams_ids" (Array Int) }
, ngrams_terms :: Var "ngrams_terms" NgramsTerms }
{ c_id :: Unit
, c_score :: Unit
, c_date :: Unit
, c_name :: Unit
, c_typename :: Unit
, c_hash_id :: Unit
, c_user_id :: Unit
, c_parent_id :: Unit
, c_category :: Unit
, c_hyperdata ::
{ hrd_abstract :: Unit
, hrd_authors :: Unit
......@@ -119,7 +128,7 @@ contextsForNgramsQuery :: ContextsForNgramsQuery
contextsForNgramsQuery
= { contexts_for_ngrams:
{ corpus_id: Var :: _ "corpus_id" Int
, ngrams_ids: Var :: _ "ngrams_ids" (Array Int) } =>>
, ngrams_terms: Var :: _ "ngrams_terms" NgramsTerms } =>>
GGQL.getFieldsStandard (Proxy :: _ Context)
}
......@@ -130,3 +139,12 @@ type NodeContextCategoryM
, node_id :: NotNull Int
, category :: Int
}
newtype NgramsTerms = NgramsTerms (Array String)
instance EncodeJson NgramsTerms where
encodeJson (NgramsTerms ngramsTerms) = encodeJson ngramsTerms
instance ArgGql String NgramsTerms
instance VarTypeName NgramsTerms where
varTypeName _ = "[String!]!"
......@@ -101,18 +101,22 @@ deleteTeamMembership session sharedFolderId teamNodeId = do
getNodeContext :: Session -> Int -> Int -> AffRESTError GQLCTX.NodeContext
getNodeContext session context_id node_id = do
{ contexts } <- queryGql session "get node context" $
GQLCTX.nodeContextQuery `withVars` { context_id, node_id }
let query = GQLCTX.nodeContextQuery `withVars` { context_id, node_id }
{ contexts } <- queryGql session "get node context" query
--liftEffect $ here.log2 "[getNodeContext] node context" contexts
case A.head contexts of
Nothing -> pure $ Left $ CustomError "no node context found"
Just context -> pure $ Right context -- TODO: error handling
-- getContextsForNgrams :: Session -> Int -> Array Int -> AffRESTError (Array GQLCTX.Context)
-- getContextsForNgrams session corpus_id ngrams_ids = do
-- { contexts_for_ngrams } <- queryGql session "get contexts for ngrams" $
-- GQLCTX.contextsForNgramsQuery `withVars` { corpus_id, ngrams_ids }
-- pure $ Right contexts_for_ngrams
type ContextsForNgramsGQL = { contexts_for_ngrams :: Array GQLCTX.Context }
getContextsForNgrams :: Session -> Int -> Array String -> AffRESTError (Array GQLCTX.Context)
getContextsForNgrams session corpus_id ngrams_terms = do
let query = GQLCTX.contextsForNgramsQuery `withVars` { corpus_id
, ngrams_terms: GQLCTX.NgramsTerms ngrams_terms }
{ contexts_for_ngrams } <- queryGql session "get contexts for ngrams" query
pure $ Right contexts_for_ngrams
--pure $ Right contexts_for_ngrams
updateNodeContextCategory :: Session -> Int -> Int -> Int -> AffRESTError Int
updateNodeContextCategory session context_id node_id category = do
......
......@@ -101,8 +101,8 @@ initialState =
, ngramsVersion: 0
}
initialStateWithVersion :: VersionedNgramsTable -> State
initialStateWithVersion (Versioned { version }) = initialState { ngramsVersion = version }
-- initialStateWithVersion :: VersionedNgramsTable -> State
-- initialStateWithVersion (Versioned { version }) = initialState { ngramsVersion = version }
setTermListSetA :: NgramsTable -> Set NgramsTerm -> TermList -> Action
setTermListSetA ngramsTable ns new_list =
......@@ -813,7 +813,7 @@ mainNgramsTable = R.createElement mainNgramsTableCpt
mainNgramsTableCpt :: R.Component MainNgramsTableProps
mainNgramsTableCpt = here.component "mainNgramsTable" cpt
where
cpt props@{ cacheState, path, treeEdit } _ = do
cpt props@{ cacheState, path } _ = do
searchQuery <- T.useFocused (_.searchQuery) (\a b -> b { searchQuery = a }) path
params <- T.useFocused (_.params) (\a b -> b { params = a }) path
cacheState' <- T.useLive T.unequal cacheState
......
......@@ -6,10 +6,9 @@ import Gargantext.Prelude
import Data.Array as A
import Data.Int as I
import Data.Maybe (Maybe(..), fromMaybe, isJust, maybe)
import Data.Maybe (Maybe(..), isJust, maybe)
import Data.Sequence as Seq
import Data.Tuple (Tuple(..))
import Data.Tuple.Nested ((/\))
import DOM.Simple (document, querySelector)
import Gargantext.Components.App.Store as AppStore
import Gargantext.Components.Bootstrap as B
......@@ -29,7 +28,6 @@ import Gargantext.Utils (getter)
import Gargantext.Utils.Range as Range
import Gargantext.Utils.Reactix as R2
import Reactix as R
import Reactix.DOM.HTML as H
import Record as Record
import Toestand as T
......@@ -176,10 +174,10 @@ hydrateStoreCpt = here.component "hydrateStore" cpt where
--let edgeWeightMin = maybe 0.0 _.weight $ A.head edgesWeightSorted
--let edgeWeightMax = maybe 100.0 _.weight $ A.last edgesWeightSorted
--let edgeWeightRange = Range.Closed { min: edgeWeightMin, max: edgeWeightMax }
let edgeWeightRange = Range.Closed {
min: 0.0
, max: I.toNumber $ Seq.length $ SigmaxT.graphEdges graph
}
-- let edgeWeightRange = Range.Closed {
-- min: 0.0
-- , max: I.toNumber $ Seq.length $ SigmaxT.graphEdges graph
-- }
let nodesSorted = A.sortWith (_.size) $ Seq.toUnfoldable $ SigmaxT.graphNodes graph
let nodeSizeMin = maybe 0.0 _.size $ A.head nodesSorted
......
......@@ -147,14 +147,8 @@ sessionPath (R.NodeAPI nt i p) = nodeTypePath nt
<> (if p == "" then "" else "/" <> p)
sessionPath (R.TreeFirstLevel nId p) = nodeTypePath Tree
<> (maybe "" (\nId' -> "/" <> show nId') nId) <> "/first-level" <> p
sessionPath (R.Search {listId, limit, offset, orderBy} Nothing) =
sessionPath $ R.NodeAPI Corpus Nothing
$ "search?list_id=" <> show listId
<> offsetUrl offset
<> limitUrl limit
<> orderUrl orderBy
sessionPath (R.Search {listId, limit, offset, orderBy} (Just corpusId)) =
sessionPath $ R.NodeAPI Corpus (Just corpusId)
sessionPath (R.Search {listId, limit, offset, orderBy} mCorpusId) =
sessionPath $ R.NodeAPI Corpus mCorpusId
$ "search?list_id=" <> show listId
<> offsetUrl offset
<> limitUrl limit
......
......@@ -38,6 +38,8 @@ type Renderer = { "type" :: String, container :: Element }
type NodeId = String
type EdgeId = String
type Label = String
type Node = (
borderColor :: String
, children :: Array String
......@@ -48,7 +50,7 @@ type Node = (
, hidden :: Boolean
, highlighted :: Boolean
, id :: NodeId
, label :: String
, label :: Label
, size :: Number
, type :: String -- available types: circle, cross, def, diamond, equilateral, pacman, square, star
, x :: Number
......
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