From 04c935268c82e10593942ce26325592c0cea506b Mon Sep 17 00:00:00 2001 From: Nicolas Pouillard <nicolas.pouillard@gmail.com> Date: Thu, 18 Oct 2018 12:37:30 +0200 Subject: [PATCH] Add CorpusLoader React component --- src/Gargantext/Components/Loader.purs | 51 +++++++ src/Gargantext/Pages/Corpus.purs | 128 ++++++------------ .../Pages/Corpus/Tabs/Documents.purs | 22 +-- src/Gargantext/Pages/Corpus/Tabs/Types.purs | 45 +++++- src/Gargantext/Pages/Layout.purs | 6 +- src/Gargantext/Pages/Layout/Actions.purs | 9 -- src/Gargantext/Pages/Layout/Specs.purs | 8 +- src/Gargantext/Pages/Layout/States.purs | 6 - 8 files changed, 151 insertions(+), 124 deletions(-) create mode 100644 src/Gargantext/Components/Loader.purs diff --git a/src/Gargantext/Components/Loader.purs b/src/Gargantext/Components/Loader.purs new file mode 100644 index 00000000..cfe052ac --- /dev/null +++ b/src/Gargantext/Components/Loader.purs @@ -0,0 +1,51 @@ +module Gargantext.Components.Loader where + +import Data.Maybe (Maybe(..)) +import Data.Either (Either(..)) +import Data.Traversable (traverse_) +import React as React +import React (ReactClass) +import Gargantext.Prelude +import Effect.Aff (Aff, launchAff, launchAff_, makeAff, nonCanceler, killFiber) +import Effect.Exception (error) + +type InnerProps a b = + { path :: a + , loaded :: Maybe b + , children :: React.Children + } + +type Props a b = { path :: a + , component :: ReactClass (InnerProps a b) + } + +createLoaderClass :: forall a b + . String + -> (a -> Aff b) + -> ReactClass (Props a b) +createLoaderClass name loader = React.component name mk + where + mk this = + pure + { state: { loaded: Nothing, fiber: Nothing } + , componentDidMount: do + logs "componentDidMount" + {path} <- React.getProps this + fiber <- launchAff $ do + newState <- loader path + makeAff $ \cb -> do + void $ React.modifyStateWithCallback + this + (_ {loaded = Just newState}) + (cb (Right unit)) + pure nonCanceler + React.modifyState this (_ { fiber = Just fiber }) + , componentWillUnmount: do + {fiber} <- React.getState this + traverse_ (launchAff_ <<< killFiber (error "Loader: killFiber")) + fiber + , render: do + {path, component} <- React.getProps this + {loaded} <- React.getState this + pure $ React.createElement component {path, loaded} [] + } diff --git a/src/Gargantext/Pages/Corpus.purs b/src/Gargantext/Pages/Corpus.purs index bafc9749..8a1a6609 100644 --- a/src/Gargantext/Pages/Corpus.purs +++ b/src/Gargantext/Pages/Corpus.purs @@ -1,119 +1,71 @@ module Gargantext.Pages.Corpus where -import Control.Monad.Trans.Class (lift) -import Data.Argonaut (class DecodeJson, decodeJson, (.?)) import Data.Either (Either(..)) -import Data.Lens (Lens', Prism', lens, prism, (?~)) -import Data.List (fromFoldable) -import Data.Maybe (Maybe(..), maybe) -import Data.Tuple (Tuple(..)) +import Data.Lens (Lens', Prism', lens, prism) +import Data.Maybe (maybe) import Effect.Aff (Aff) +import React as React +import React (ReactClass, ReactElement) import React.DOM (div, h3, hr, i, p, text) import React.DOM.Props (className, style) -import Thermite ( Render, Spec, PerformAction, focus, cmapProps - , simpleSpec, modifyState, noState) +import Thermite ( Render, Spec, createClass, defaultPerformAction, focus + , simpleSpec, noState ) -------------------------------------------------------- import Gargantext.Prelude import Gargantext.Components.Node (NodePoly(..)) +import Gargantext.Components.Loader as Loader +import Gargantext.Components.Loader (createLoaderClass) import Gargantext.Config (toUrl, NodeType(..), End(..)) import Gargantext.Config.REST (get) -import Gargantext.Pages.Corpus.Tabs.Types as Tabs -import Gargantext.Pages.Corpus.Tabs.States as Tabs -import Gargantext.Pages.Corpus.Tabs.Actions as Tabs -import Gargantext.Pages.Corpus.Tabs.Specs as Tabs +import Gargantext.Pages.Corpus.Tabs.Types (CorpusInfo(..), corpusInfoDefault) +import Gargantext.Pages.Corpus.Tabs.Types (Props) as Tabs +import Gargantext.Pages.Corpus.Tabs.States (State, initialState) as Tabs +import Gargantext.Pages.Corpus.Tabs.Actions (Action) as Tabs +import Gargantext.Pages.Corpus.Tabs.Specs (statefulTabs) as Tabs ------------------------------------------------------------------- type Props = Tabs.Props -type HeaderState = { info :: Maybe (NodePoly CorpusInfo) } -type State = { headerView :: HeaderState - , tabsView :: Tabs.State +type State = { tabsView :: Tabs.State } initialState :: State -initialState = { headerView : { info : Nothing } - , tabsView : Tabs.initialState +initialState = { tabsView : Tabs.initialState } ------------------------------------------------------------------------ -_info :: forall a b. Lens' { info :: a | b } a -_info = lens (\s -> s.info) (\s ss -> s{info = ss}) - -_headerView :: forall a b. Lens' { headerView :: a | b } a -_headerView = lens (\s -> s.headerView) (\s ss -> s{headerView = ss}) - _tabsView :: forall a b. Lens' { tabsView :: a | b } a _tabsView = lens (\s -> s.tabsView) (\s ss -> s{tabsView = ss}) ------------------------------------------------------------------------ -data HeaderAction = Load Int data Action - = HeaderA HeaderAction - | TabsA Tabs.Action - -_headerAction :: Prism' Action HeaderAction -_headerAction = prism HeaderA \ action -> - case action of - HeaderA haction -> Right haction - _-> Left action + = TabsA Tabs.Action _tabsAction :: Prism' Action Tabs.Action _tabsAction = prism TabsA \ action -> case action of TabsA taction -> Right taction - _-> Left action - - -_loadAction :: Prism' HeaderAction Int -_loadAction = prism Load \ action -> - case action of - Load x -> Right x -- _-> Left action ------------------------------------------------------------------------ -newtype CorpusInfo = CorpusInfo { title :: String - , desc :: String - , query :: String - , authors :: String - , chart :: (Maybe (Array Number)) - } - -corpusInfoDefault :: NodePoly CorpusInfo -corpusInfoDefault = NodePoly { id : 0 - , typename : 0 - , userId : 0 - , parentId : 0 - , name : "Default name" - , date : " Default date" - , hyperdata : CorpusInfo - { title : "Default title" - , desc : " Default desc" - , query : " Default Query" - , authors : " Author(s): default" - , chart : Nothing - } - } - -instance decodeCorpusInfo :: DecodeJson CorpusInfo where - decodeJson json = do - obj <- decodeJson json - title <- obj .? "title" - desc <- obj .? "desc" - query <- obj .? "query" - authors <- obj .? "authors" - chart <- obj .? "chart" - pure $ CorpusInfo {title, desc, query, authors, chart} - ------------------------------------------------------------------------- -layout :: Spec State Props Action -layout = cmapProps (const {}) (focus _headerView _headerAction corpusHeaderSpec) - <> focus _tabsView _tabsAction Tabs.statefulTabs - -corpusHeaderSpec :: Spec HeaderState {} HeaderAction -corpusHeaderSpec = simpleSpec performAction render +layout :: Spec {} {nodeId :: Int} Void +layout = simpleSpec defaultPerformAction render where - render :: Render HeaderState {} HeaderAction - render dispatch _ state _ = + render :: Render {} {nodeId :: Int} Void + render _ {nodeId} _ _ = + [ nodeLoader { path: nodeId + , component: createClass "Layout" layout' initialState + } ] + +layout' :: Spec State Props Action +layout' = noState corpusHeaderSpec + <> focus _tabsView _tabsAction Tabs.statefulTabs + +corpusHeaderSpec :: Spec {} Props Void +corpusHeaderSpec = simpleSpec defaultPerformAction render + where + render :: Render {} Props Void + render dispatch {loaded} _ _ = [ div [className "row"] [ div [className "col-md-3"] [ h3 [] [text "Corpus " <> text title] ] , div [className "col-md-9"] [ hr [style {height : "2px",backgroundColor : "black"}] ] @@ -143,14 +95,16 @@ corpusHeaderSpec = simpleSpec performAction render , date: date' , hyperdata : CorpusInfo corpus } - = maybe corpusInfoDefault identity state.info + = maybe corpusInfoDefault identity loaded ------------------------------------------------------------------------ -performAction :: PerformAction HeaderState {} HeaderAction -performAction (Load nId) _ _ = do - node <- lift $ getNode nId - void $ modifyState $ _info ?~ node - logs $ "Node Corpus fetched." getNode :: Int -> Aff (NodePoly CorpusInfo) getNode = get <<< toUrl Back Node +-- MOCK getNode = const $ pure corpusInfoDefault + +nodeLoaderClass :: ReactClass (Loader.Props Int (NodePoly CorpusInfo)) +nodeLoaderClass = createLoaderClass "NodeLoader" getNode + +nodeLoader :: Loader.Props Int (NodePoly CorpusInfo) -> ReactElement +nodeLoader = React.createLeafElement nodeLoaderClass diff --git a/src/Gargantext/Pages/Corpus/Tabs/Documents.purs b/src/Gargantext/Pages/Corpus/Tabs/Documents.purs index f94165e3..af34414d 100644 --- a/src/Gargantext/Pages/Corpus/Tabs/Documents.purs +++ b/src/Gargantext/Pages/Corpus/Tabs/Documents.purs @@ -5,6 +5,7 @@ import Data.Argonaut (class DecodeJson, class EncodeJson, decodeJson, jsonEmptyO import Data.Generic.Rep (class Generic) import Data.Generic.Rep.Show (genericShow) +import Data.Maybe (maybe) import Data.Tuple (Tuple(..)) import Effect.Aff (Aff) import React.DOM (a, br', div, input, p, text) @@ -17,6 +18,8 @@ import Gargantext.Config.REST (get, post) import Gargantext.Utils.DecodeMaybe ((.|)) import Gargantext.Components.Charts.Options.ECharts (chart) import Gargantext.Components.Table as T +import Gargantext.Components.Node (NodePoly(..)) +import Gargantext.Pages.Corpus.Tabs.Types import Gargantext.Pages.Corpus.Dashboard (globalPublis) ------------------------------------------------------------------------ -- TODO: Pagination Details are not available from the BackEnd @@ -26,14 +29,6 @@ import Gargantext.Pages.Corpus.Dashboard (globalPublis) -- TODO: Filter is Pending -- TODO: When a pagination link is clicked, reload data. -type Props = - { totalRecords :: Int - , nodeId :: Int -- /!\ When changing the pages of the Table, NodeId - -- is needed to reload Data (other solution is using - -- NodeId as a parameter - -- NP,TODO this should not be in state - } - type State = {} type Action = Void @@ -120,7 +115,7 @@ layoutDocview :: Spec State Props Action layoutDocview = simpleSpec absurd render where render :: Render State Props Action - render dispatch {nodeId, totalRecords} _ _ = + render dispatch {path, loaded} _ _ = [ div [className "container1"] [ div [className "row"] [ chart globalPublis @@ -138,7 +133,12 @@ layoutDocview = simpleSpec absurd render , "Source" , "Delete" ] - , totalRecords + , totalRecords: maybe 47361 -- TODO + identity + ((\(NodePoly n) -> n.hyperdata) + >>> + (\(CorpusInfo c) -> c.totalRecords) + <$> loaded) } ] ] @@ -147,7 +147,7 @@ layoutDocview = simpleSpec absurd render where loadRows {offset, limit} = do _ <- logs "loading documents page" - res <- loadPage {nodeId,offset,limit} + res <- loadPage {nodeId: path,offset,limit} _ <- logs "OK: loading page documents." pure $ (\(DocumentsView r) -> diff --git a/src/Gargantext/Pages/Corpus/Tabs/Types.purs b/src/Gargantext/Pages/Corpus/Tabs/Types.purs index d6958d43..212513d4 100644 --- a/src/Gargantext/Pages/Corpus/Tabs/Types.purs +++ b/src/Gargantext/Pages/Corpus/Tabs/Types.purs @@ -1,6 +1,49 @@ module Gargantext.Pages.Corpus.Tabs.Types where -type Props = {nodeId :: Int, totalRecords :: Int} +import Data.Argonaut (class DecodeJson, decodeJson, (.?)) +import Data.Maybe (Maybe(..)) +-------------------------------------------------------- +import Gargantext.Prelude +import Gargantext.Components.Node (NodePoly(..)) + +newtype CorpusInfo = CorpusInfo { title :: String + , desc :: String + , query :: String + , authors :: String + , chart :: (Maybe (Array Number)) + , totalRecords :: Int + } + +corpusInfoDefault :: NodePoly CorpusInfo +corpusInfoDefault = NodePoly { id : 0 + , typename : 0 + , userId : 0 + , parentId : 0 + , name : "Default name" + , date : " Default date" + , hyperdata : CorpusInfo + { title : "Default title" + , desc : " Default desc" + , query : " Default Query" + , authors : " Author(s): default" + , chart : Nothing + , totalRecords : 0 + } + } + +instance decodeCorpusInfo :: DecodeJson CorpusInfo where + decodeJson json = do + obj <- decodeJson json + title <- obj .? "title" + desc <- obj .? "desc" + query <- obj .? "query" + authors <- obj .? "authors" + chart <- obj .? "chart" + let totalRecords = 47361 -- TODO + pure $ CorpusInfo {title, desc, query, authors, chart, totalRecords} + +-- TODO type Props = {nodeId :: Int, info :: Maybe (NodePoly CorpusInfo) } +type Props = {path :: Int, loaded :: Maybe (NodePoly CorpusInfo) } -- TODO include Gargantext.Pages.Corpus.Tabs.States -- TODO include Gargantext.Pages.Corpus.Tabs.Actions diff --git a/src/Gargantext/Pages/Layout.purs b/src/Gargantext/Pages/Layout.purs index a6e5692d..e242f815 100644 --- a/src/Gargantext/Pages/Layout.purs +++ b/src/Gargantext/Pages/Layout.purs @@ -6,10 +6,7 @@ import Gargantext.Pages.Layout.Actions (Action(..)) import Gargantext.Pages.Layout.Specs.AddCorpus as AC -- import Gargantext.Pages.Corpus.Tabs as TV -import Gargantext.Pages.Corpus as Corpus import Gargantext.Pages.Corpus.Document as Document -import Gargantext.Pages.Corpus.Tabs.Documents as D -import Gargantext.Pages.Corpus.Tabs.Actions as TabsA import Gargantext.Pages.Corpus.Graph as GE -- import Gargantext.Pages.Corpus.Tabs.Terms.NgramsTable as NG @@ -38,8 +35,7 @@ dispatchAction dispatcher _ AddCorpus = do dispatcher $ AddCorpusA AC.LoadDatabaseDetails dispatchAction dispatcher _ (Corpus n) = do - dispatcher $ SetRoute $ Corpus n - dispatcher $ CorpusAction $ Corpus.HeaderA $ Corpus.Load n + dispatcher $ SetRoute $ Corpus n dispatchAction dispatcher _ SearchView = do dispatcher $ SetRoute SearchView diff --git a/src/Gargantext/Pages/Layout/Actions.purs b/src/Gargantext/Pages/Layout/Actions.purs index 9ce406cb..64d89300 100644 --- a/src/Gargantext/Pages/Layout/Actions.purs +++ b/src/Gargantext/Pages/Layout/Actions.purs @@ -13,7 +13,6 @@ import Gargantext.Components.Modals.Modal (modalShow) import Gargantext.Components.Tree as Tree import Gargantext.Pages.Annuaire as Annuaire import Gargantext.Pages.Annuaire.User.Users as U -import Gargantext.Pages.Corpus as Corpus import Gargantext.Pages.Corpus.Document as D import Gargantext.Pages.Corpus.Graph as GE import Gargantext.Pages.Layout.Specs.AddCorpus as AC @@ -29,7 +28,6 @@ data Action | LoginA LN.Action | SetRoute Routes | TreeViewA Tree.Action - | CorpusAction Corpus.Action | SearchA S.Action | Search String | AddCorpusA AC.Action @@ -76,7 +74,6 @@ performAction Initialize _ state = void do performAction (LoginA _) _ _ = pure unit performAction (AddCorpusA _) _ _ = pure unit -performAction (CorpusAction _) _ _ = pure unit performAction (SearchA _) _ _ = pure unit performAction (UserPageA _) _ _ = pure unit performAction (DocumentViewA _) _ _ = pure unit @@ -98,12 +95,6 @@ _addCorpusAction = prism AddCorpusA \action -> AddCorpusA caction -> Right caction _-> Left action -_corpusAction :: Prism' Action Corpus.Action -_corpusAction = prism CorpusAction \action -> - case action of - CorpusAction caction -> Right caction - _-> Left action - _searchAction :: Prism' Action S.Action _searchAction = prism SearchA \action -> case action of diff --git a/src/Gargantext/Pages/Layout/Specs.purs b/src/Gargantext/Pages/Layout/Specs.purs index 8053e375..a4f46eb2 100644 --- a/src/Gargantext/Pages/Layout/Specs.purs +++ b/src/Gargantext/Pages/Layout/Specs.purs @@ -23,10 +23,10 @@ import Gargantext.Pages.Corpus.Dashboard as Dsh import Gargantext.Pages.Corpus.Graph as GE import Gargantext.Pages.Corpus.Tabs.Terms.NgramsTable as NG import Gargantext.Pages.Home as L -import Gargantext.Pages.Layout.Actions (Action(..), _corpusAction, _addCorpusAction, _documentViewAction, _graphExplorerAction, _loginAction, _searchAction, _treeAction, _userPageAction, performAction, _annuaireAction) +import Gargantext.Pages.Layout.Actions (Action(..), _addCorpusAction, _documentViewAction, _graphExplorerAction, _loginAction, _searchAction, _treeAction, _userPageAction, performAction, _annuaireAction) import Gargantext.Pages.Layout.Specs.AddCorpus as AC import Gargantext.Pages.Layout.Specs.Search as S -import Gargantext.Pages.Layout.States (AppState, _corpusState, _addCorpusState, _documentViewState, _graphExplorerState, _loginState, _searchState, _treeState, _userPageState, _annuaireState) +import Gargantext.Pages.Layout.States (AppState, _addCorpusState, _documentViewState, _graphExplorerState, _loginState, _searchState, _treeState, _userPageState, _annuaireState) import Gargantext.Router (Routes(..)) layoutSpec :: Spec AppState {} Action @@ -55,9 +55,7 @@ pagesComponent s = case s.currentRoute of selectSpec Login = focus _loginState _loginAction LN.renderSpec selectSpec (Folder i) = layout0 $ noState F.layoutFolder - selectSpec (Corpus i) = layout0 $ - cmapProps (const {nodeId: i, totalRecords: 47361}) -- TODO - (focus _corpusState _corpusAction Corpus.layout) + selectSpec (Corpus i) = layout0 $ cmapProps (const {nodeId: i}) $ noState Corpus.layout selectSpec AddCorpus = layout0 $ focus _addCorpusState _addCorpusAction AC.layoutAddcorpus selectSpec SearchView = layout0 $ focus _searchState _searchAction S.searchSpec selectSpec (Document i) = layout0 $ focus _documentViewState _documentViewAction Annotation.docview diff --git a/src/Gargantext/Pages/Layout/States.purs b/src/Gargantext/Pages/Layout/States.purs index f797835b..8fe330c8 100644 --- a/src/Gargantext/Pages/Layout/States.purs +++ b/src/Gargantext/Pages/Layout/States.purs @@ -7,7 +7,6 @@ import Data.Maybe (Maybe(Just)) import Gargantext.Components.Login as LN import Gargantext.Components.Tree as Tree -import Gargantext.Pages.Corpus as Corpus import Gargantext.Pages.Corpus.Document as D import Gargantext.Pages.Annuaire as Annuaire import Gargantext.Pages.Corpus.Tabs.Documents as DV @@ -20,7 +19,6 @@ import Gargantext.Router (Routes(..)) type AppState = { currentRoute :: Maybe Routes , loginState :: LN.State - , corpus :: Corpus.State , addCorpusState :: AC.State , docViewState :: DV.State , searchState :: S.State @@ -38,7 +36,6 @@ type AppState = initAppState :: AppState initAppState = { currentRoute : Just Home - , corpus : Corpus.initialState , loginState : LN.initialState , addCorpusState : AC.initialState , docViewState : DV.initialState @@ -61,9 +58,6 @@ _loginState = lens (\s -> s.loginState) (\s ss -> s{loginState = ss}) _addCorpusState :: Lens' AppState AC.State _addCorpusState = lens (\s -> s.addCorpusState) (\s ss -> s{addCorpusState = ss}) -_corpusState :: Lens' AppState Corpus.State -_corpusState = lens (\s -> s.corpus) (\s ss -> s{corpus = ss}) - _docViewState :: Lens' AppState DV.State _docViewState = lens (\s -> s.docViewState) (\s ss -> s{docViewState = ss}) -- 2.21.0