Commit 4841cdf1 authored by Nicolas Pouillard's avatar Nicolas Pouillard Committed by Alexandre Delanoë

[NGRAMS-REPO] fetch the default list in loader

parent 6df1daea
......@@ -62,12 +62,13 @@ type Props a mode = Loader.InnerProps Int a ( mode :: mode )
type PageParams =
{ nodeId :: Int
, listIds :: Array Int
, params :: T.Params
, tabType :: TabType
}
initialPageParams :: Int -> TabType -> PageParams
initialPageParams nodeId tabType = {nodeId, params: T.initialParams, tabType}
initialPageParams :: Int -> Array Int -> TabType -> PageParams
initialPageParams nodeId listIds tabType = {nodeId, listIds, params: T.initialParams, tabType}
type Props' = Loader.InnerProps PageParams VersionedNgramsTable ()
......@@ -537,14 +538,14 @@ ngramsTableSpec = simpleSpec performAction render
-- patch the root of the child to be equal to the root of the parent.
render :: Render State Props' Action
render dispatch { path: {nodeId, tabType}
render dispatch { path: {nodeId, listIds, tabType}
, loaded: Versioned { data: initTable }
, dispatch: loaderDispatch }
{ ngramsTablePatch, ngramsParent, ngramsChildren, searchQuery }
_reactChildren =
[ T.tableElt
{ rows
, setParams: \params -> loaderDispatch (Loader.SetPath {nodeId, params, tabType})
, setParams: \params -> loaderDispatch (Loader.SetPath {nodeId, listIds, params, tabType})
, container: tableContainer {searchQuery, dispatch, ngramsParent, ngramsChildren, ngramsTable}
, colNames:
T.ColumnName <$>
......
......@@ -11,6 +11,7 @@ module Gargantext.Config where
import Prelude
import Data.Argonaut (class DecodeJson, decodeJson)
import Data.Foldable (foldMap)
import Data.Generic.Rep (class Generic)
import Data.Generic.Rep.Show (genericShow)
import Data.Map (Map)
......@@ -126,11 +127,12 @@ pathUrl c (Tab t o l s) i =
pathUrl c (Children n o l s) i =
pathUrl c (NodeAPI Node) i <>
"/" <> "children?type=" <> show n <> offsetUrl o <> limitUrl l <> orderUrl s
pathUrl c (GetNgrams t o l listid) i =
pathUrl c (GetNgrams t o l listIds listTypeId) i =
pathUrl c (NodeAPI Node) i <> "/" <> tabTypeNgramsGet t
<> offsetUrl o <> limitUrl l <> listid'
<> offsetUrl o <> limitUrl l <> listIds' <> listTypeId'
where
listid' = maybe "" (\x -> "&list=" <> show x) listid
listIds' = foldMap (\x -> "&list=" <> show x) listIds
listTypeId' = foldMap (\x -> "&listType=" <> show x) listTypeId
pathUrl c (PutNgrams t listid) i =
pathUrl c (NodeAPI Node) i <> "/" <> tabTypeNgramsPut t <> listid'
where
......@@ -174,6 +176,7 @@ data NodeType = NodeUser
| Node
| Nodes
| Tree
| NodeList
instance showNodeType :: Show NodeType where
......@@ -192,12 +195,15 @@ instance showNodeType :: Show NodeType where
show Node = "Node"
show Nodes = "Nodes"
show Tree = "NodeTree"
show NodeList = "NodeList"
type ListId = Int
data Path
= Auth
| Tab TabType Offset Limit (Maybe OrderBy)
| Children NodeType Offset Limit (Maybe OrderBy)
| GetNgrams TabType Offset Limit (Maybe TermList)
| GetNgrams TabType Offset Limit (Array ListId) (Maybe TermList)
| PutNgrams TabType (Maybe TermList)
| NodeAPI NodeType
| Search { {-id :: Int
......@@ -283,6 +289,7 @@ nodeTypeUrl Nodes = "nodes"
nodeTypeUrl NodeUser = "user"
nodeTypeUrl NodeContact = "contact"
nodeTypeUrl Tree = "tree"
nodeTypeUrl NodeList = "list"
readNodeType :: String -> NodeType
readNodeType "NodeAnnuaire" = Annuaire
......@@ -298,6 +305,7 @@ readNodeType "NodeCorpusV3" = CorpusV3
readNodeType "NodeUser" = NodeUser
readNodeType "NodeContact" = NodeContact
readNodeType "Tree" = Tree
readNodeType "NodeList" = NodeList
readNodeType _ = Error
{-
------------------------------------------------------------
......
......@@ -35,15 +35,19 @@ modeTabType Communication = PTabCommunication
type Props = NT.Props Contact Mode
-- TODO: Move to Components.NgramsTable
getTable :: { tabType :: TabType, nodeId :: Int, offset :: Offset, limit :: Limit }
getTable :: { tabType :: TabType
, nodeId :: Int
, listIds :: Array Int
, offset :: Offset
, limit :: Limit }
-> Aff NT.VersionedNgramsTable
getTable {tabType, nodeId, offset, limit} =
get $ toUrl Back (GetNgrams tabType offset limit Nothing) (Just nodeId)
getTable {tabType, nodeId, listIds, offset, limit} =
get $ toUrl Back (GetNgrams tabType offset limit listIds Nothing) (Just nodeId)
-- TODO: Move to Components.NgramsTable
loadPage :: NT.PageParams -> Aff NT.VersionedNgramsTable
loadPage {nodeId, tabType, params: {offset, limit}} =
getTable {tabType, nodeId, offset, limit}
loadPage {nodeId, listIds, tabType, params: {offset, limit}} =
getTable {tabType, nodeId, listIds, offset, limit}
-- TODO this ignores orderBy
-- TODO: Move to Components.NgramsTable?
......@@ -64,7 +68,7 @@ ngramsTableSpec = simpleSpec defaultPerformAction render
render :: Render {} Props Void
render _ {path: nodeId, mode} _ _ =
-- TODO: ignored loaded
[ ngramsLoader { path: NT.initialPageParams nodeId tabType
[ ngramsLoader { path: NT.initialPageParams nodeId [] tabType
, component: ngramsTableClass
} ]
where
......
module Gargantext.Pages.Corpus where
import Data.Array (head)
import Data.Maybe (Maybe(..))
import Effect.Aff (Aff)
import Effect.Aff (Aff, throwError)
import Effect.Exception (error)
import React as React
import React (ReactClass, ReactElement)
import Thermite (Spec, Render, simpleSpec, createClass, defaultPerformAction)
......@@ -12,9 +14,9 @@ import Gargantext.Components.Node (NodePoly(..))
import Gargantext.Components.Loader as Loader
import Gargantext.Components.Loader (createLoaderClass)
import Gargantext.Components.Table as Table
import Gargantext.Config (toUrl, NodeType(..), End(..))
import Gargantext.Config (toUrl, Path(..), NodeType(..), End(..))
import Gargantext.Config.REST (get)
import Gargantext.Pages.Corpus.Tabs.Types (CorpusInfo(..))
import Gargantext.Pages.Corpus.Tabs.Types (CorpusData, CorpusInfo(..))
import Gargantext.Pages.Corpus.Tabs.Types (Props) as Tabs
import Gargantext.Pages.Corpus.Tabs.Specs (pureTabs) as Tabs
-------------------------------------------------------------------
......@@ -37,7 +39,7 @@ corpusHeaderSpec :: Spec {} Props Void
corpusHeaderSpec = simpleSpec defaultPerformAction render
where
render :: Render {} Props Void
render dispatch {loaded} _ _ =
render dispatch {loaded: {corpusNode}} _ _ =
Table.renderTableHeaderLayout
{ title: "Corpus " <> title
, desc: corpus.desc
......@@ -50,15 +52,22 @@ corpusHeaderSpec = simpleSpec defaultPerformAction render
, date: date'
, hyperdata : CorpusInfo corpus
}
= loaded
= corpusNode
------------------------------------------------------------------------
getCorpus :: Int -> Aff (NodePoly CorpusInfo)
getCorpus = get <<< toUrl Back Corpus <<< Just
getCorpus :: Int -> Aff CorpusData
getCorpus corpusId = do
corpusNode <- get $ toUrl Back Corpus $ Just corpusId
defaultListIds <- get $ toUrl Back (Children NodeList 0 1 Nothing) $ Just corpusId
case (head defaultListIds :: Maybe (NodePoly Unit)) of
Just (NodePoly { id: defaultListId }) ->
pure {corpusNode, defaultListId}
Nothing ->
throwError $ error "Missing default list"
corpusLoaderClass :: ReactClass (Loader.Props Int (NodePoly CorpusInfo))
corpusLoaderClass :: ReactClass (Loader.Props Int CorpusData)
corpusLoaderClass = createLoaderClass "CorpusLoader" getCorpus
corpusLoader :: Loader.Props' Int (NodePoly CorpusInfo) -> ReactElement
corpusLoader :: Loader.Props' Int CorpusData -> ReactElement
corpusLoader props = React.createElement corpusLoaderClass props []
......@@ -16,7 +16,7 @@ import Gargantext.Prelude
import Gargantext.Config (CTabNgramType(..), End(..), Offset, Limit, Path(..), TabSubType(..), TabType(..), toUrl)
import Gargantext.Config.REST (get)
import Gargantext.Components.Loader as Loader
import Gargantext.Pages.Corpus.Tabs.Types (CorpusInfo)
import Gargantext.Pages.Corpus.Tabs.Types (CorpusData)
data Mode = Authors | Sources | Institutes | Terms
......@@ -27,7 +27,7 @@ instance showMode :: Show Mode where
derive instance eqMode :: Eq Mode
type Props = NT.Props (NodePoly CorpusInfo) Mode
type Props = NT.Props CorpusData Mode
modeTabType :: Mode -> CTabNgramType
modeTabType Authors = CTabAuthors
......@@ -35,15 +35,19 @@ modeTabType Sources = CTabSources
modeTabType Institutes = CTabInstitutes
modeTabType Terms = CTabTerms
getTable :: { tabType :: TabType, nodeId :: Int, offset :: Offset, limit :: Limit }
getTable :: { tabType :: TabType
, nodeId :: Int
, listIds :: Array Int
, offset :: Offset
, limit :: Limit }
-> Aff NT.VersionedNgramsTable
getTable {tabType, nodeId, offset, limit} =
get $ toUrl Back (GetNgrams tabType offset limit Nothing) (Just nodeId)
getTable {tabType, nodeId, listIds, offset, limit} =
get $ toUrl Back (GetNgrams tabType offset limit listIds Nothing) (Just nodeId)
-- TODO: Move to Components.NgramsTable?
loadPage :: NT.PageParams -> Aff NT.VersionedNgramsTable
loadPage {nodeId, tabType, params: {offset, limit}} =
getTable {tabType, nodeId, offset, limit}
loadPage {nodeId, listIds, tabType, params: {offset, limit}} =
getTable {tabType, nodeId, listIds, offset, limit}
-- TODO this ignores orderBy
-- TODO: Move to Components.NgramsTable?
......@@ -62,9 +66,8 @@ ngramsTableSpec :: Spec {} Props Void
ngramsTableSpec = simpleSpec defaultPerformAction render
where
render :: Render {} Props Void
render _ {path: nodeId, mode} _ _ =
-- TODO: ignored loaded param
[ ngramsLoader { path: NT.initialPageParams nodeId tabType
render _ {path: nodeId, loaded: {defaultListId}, mode} _ _ =
[ ngramsLoader { path: NT.initialPageParams nodeId [defaultListId] tabType
, component: ngramsTableClass
} ]
where
......
......@@ -43,8 +43,10 @@ instance decodeCorpusInfo :: DecodeJson CorpusInfo where
let totalRecords = 47361 -- TODO
pure $ CorpusInfo {title, desc, query, authors, chart, totalRecords}
type CorpusData = {corpusNode :: NodePoly CorpusInfo, defaultListId :: Int}
-- TODO type Props = {nodeId :: Int, info :: Maybe (NodePoly CorpusInfo) }
type PropsRow = Loader.InnerPropsRow Int (NodePoly CorpusInfo) ()
type PropsRow = Loader.InnerPropsRow Int CorpusData ()
type Props = Record PropsRow
-- TODO include Gargantext.Pages.Corpus.Tabs.States
......
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