Commit 3e6c30a0 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[Corpus] Backend connection ok, next: facets.

parent 7da3fe09
...@@ -13,7 +13,7 @@ import React (ReactElement) ...@@ -13,7 +13,7 @@ import React (ReactElement)
import React.DOM (div, h1, h3, hr, i, p, text, thead, tbody, input, br', b, b', tr, th, table, td, a) import React.DOM (div, h1, h3, hr, i, p, text, thead, tbody, input, br', b, b', tr, th, table, td, a)
import React.DOM.Props (_type, className, href, onChange, onClick, scope, selected, value, style) import React.DOM.Props (_type, className, href, onChange, onClick, scope, selected, value, style)
import Thermite (Render, Spec import Thermite (Render, Spec
, simpleSpec, defaultPerformAction , simpleSpec
, PerformAction, modifyState) , PerformAction, modifyState)
import Effect.Console (log) import Effect.Console (log)
import Effect.Aff (Aff) import Effect.Aff (Aff)
......
module Gargantext.Pages.Corpus where module Gargantext.Pages.Corpus where
import Data.Maybe (Maybe(..), maybe)
import Prelude hiding (div) import Prelude hiding (div)
import Control.Monad.Trans.Class (lift)
import Data.Maybe (Maybe(..), maybe)
import Data.Lens (Lens', Prism', lens, prism, (?~))
import Data.Either (Either(..))
import Data.Argonaut (class DecodeJson, decodeJson, (.?)) import Data.Argonaut (class DecodeJson, decodeJson, (.?))
import Effect.Aff (Aff)
import Effect.Class (liftEffect)
import Effect.Console (log)
import Gargantext.Config (toUrl, NodeType(..), End(..))
import Gargantext.Config.REST (get)
import Gargantext.Components.Charts.Options.ECharts (chart) import Gargantext.Components.Charts.Options.ECharts (chart)
import Gargantext.Pages.Corpus.Doc.Facets.Dashboard (globalPublis) import Gargantext.Pages.Corpus.Doc.Facets.Dashboard (globalPublis)
import Gargantext.Pages.Corpus.Doc.Facets as Tab import Gargantext.Pages.Corpus.Doc.Facets as Tab
import React.DOM (div, h3, hr, i, p, text) import React.DOM (div, h3, hr, i, p, text)
import React.DOM.Props (className, style) import React.DOM.Props (className, style)
import Thermite (Render, Spec, defaultPerformAction, simpleSpec) import Thermite ( Render, Spec, PerformAction
, defaultPerformAction, simpleSpec, modifyState)
------------------------------------------------------------------- -------------------------------------------------------------------
type State = { info :: Maybe (NodePoly CorpusInfo)}
type State = { info :: Maybe CorpusInfo
}
initialState :: State initialState :: State
initialState = { info : Nothing } initialState = { info : Nothing }
data Action = Load Int data Action = Load Int
newtype Node a = Node { id :: Int newtype NodePoly a = NodePoly { id :: Int
, typename :: Int , typename :: Int
, userId :: Int , userId :: Int
, parentId :: Int , parentId :: Int
, name :: String , name :: String
, date :: String , date :: String
, hyperdata :: a , hyperdata :: a
} }
newtype CorpusInfo = CorpusInfo { title :: String newtype CorpusInfo = CorpusInfo { title :: String
, desc :: String , desc :: String
, query :: String , query :: String
, date :: String , authors :: String
, authors :: String , chart :: (Maybe (Array Number))
, chart :: (Maybe (Array Number)) }
}
corpusInfoDefault :: NodePoly CorpusInfo
corpusInfoDefault :: CorpusInfo corpusInfoDefault = NodePoly { id : 0
corpusInfoDefault = CorpusInfo , typename : 0
{ title : "Global Publications" , userId : 0
, desc : " Hal Database" , parentId : 0
, query : " Query: all publications" , name : "Default name"
, date : " June. 26 2018, 10:59 am" , date : " Default date"
, authors : " Author(s): first.last name" , hyperdata : CorpusInfo
, chart : Nothing { title : "Default title"
} , desc : " Default desc"
, query : " Default Query"
, authors : " Author(s): default"
, chart : Nothing
}
}
instance decodeCorpusInfo :: DecodeJson CorpusInfo where instance decodeCorpusInfo :: DecodeJson CorpusInfo where
decodeJson json = do decodeJson json = do
...@@ -53,13 +69,12 @@ instance decodeCorpusInfo :: DecodeJson CorpusInfo where ...@@ -53,13 +69,12 @@ instance decodeCorpusInfo :: DecodeJson CorpusInfo where
title <- obj .? "title" title <- obj .? "title"
desc <- obj .? "desc" desc <- obj .? "desc"
query <- obj .? "query" query <- obj .? "query"
date <- obj .? "date"
authors <- obj .? "authors" authors <- obj .? "authors"
chart <- obj .? "chart" chart <- obj .? "chart"
pure $ CorpusInfo {title, desc, query, date, authors, chart} pure $ CorpusInfo {title, desc, query, authors, chart}
instance decodeNode :: (DecodeJson a) => DecodeJson (Node a) where instance decodeNode :: (DecodeJson a) => DecodeJson (NodePoly a) where
decodeJson json = do decodeJson json = do
obj <- decodeJson json obj <- decodeJson json
id <- obj .? "id" id <- obj .? "id"
...@@ -72,7 +87,7 @@ instance decodeNode :: (DecodeJson a) => DecodeJson (Node a) where ...@@ -72,7 +87,7 @@ instance decodeNode :: (DecodeJson a) => DecodeJson (Node a) where
hyperdata <- obj .? "hyperdata" hyperdata <- obj .? "hyperdata"
hyperdata' <- decodeJson hyperdata hyperdata' <- decodeJson hyperdata
pure $ Node { id : id pure $ NodePoly { id : id
, typename : typename , typename : typename
, userId : userId , userId : userId
, parentId : parentId , parentId : parentId
...@@ -82,16 +97,17 @@ instance decodeNode :: (DecodeJson a) => DecodeJson (Node a) where ...@@ -82,16 +97,17 @@ instance decodeNode :: (DecodeJson a) => DecodeJson (Node a) where
} }
------------------------------------------------------------------------
layout :: Spec State {} Action layout :: Spec State {} Action
layout = corpusSpec -- <> Tab.pureTab1 layout = corpusSpec -- <> Tab.pureTab1
corpusSpec :: Spec State {} Action corpusSpec :: Spec State {} Action
corpusSpec = simpleSpec defaultPerformAction render corpusSpec = simpleSpec performAction render
where where
render :: Render State {} Action render :: Render State {} Action
render dispatch _ state _ = render dispatch _ state _ =
[ div [className "row"] [ div [className "row"]
[ div [className "col-md-3"] [ h3 [] [text corpus.title] ] [ div [className "col-md-3"] [ h3 [] [text "Corpus " <> text title] ]
, div [className "col-md-9"] [ hr [style {height : "2px",backgroundColor : "black"}] ] , div [className "col-md-9"] [ hr [style {height : "2px",backgroundColor : "black"}] ]
] ]
, div [className "row"] [ div [className "jumbotron1", style {padding : "12px 0px 20px 12px"}] , div [className "row"] [ div [className "jumbotron1", style {padding : "12px 0px 20px 12px"}]
...@@ -105,7 +121,7 @@ corpusSpec = simpleSpec defaultPerformAction render ...@@ -105,7 +121,7 @@ corpusSpec = simpleSpec defaultPerformAction render
] ]
, div [ className "col-md-4 content"] , div [ className "col-md-4 content"]
[ p [] [ i [className "fa fa-calendar"] [] [ p [] [ i [className "fa fa-calendar"] []
, text corpus.date , text date'
] ]
, p [] [ i [className "fa fa-user"] [] , p [] [ i [className "fa fa-user"] []
, text corpus.authors , text corpus.authors
...@@ -113,8 +129,32 @@ corpusSpec = simpleSpec defaultPerformAction render ...@@ -113,8 +129,32 @@ corpusSpec = simpleSpec defaultPerformAction render
] ]
] ]
] ]
-- , chart globalPublis TODO add chart data in state --, chart globalPublis -- TODO add chart data in state
] ]
where where
CorpusInfo corpus = maybe corpusInfoDefault identity state.info NodePoly { name: title
, date: date'
, hyperdata : CorpusInfo corpus
}
= maybe corpusInfoDefault identity state.info
------------------------------------------------------------------------
performAction :: PerformAction State {} Action
performAction (Load nId) _ _ = do
eitherInfo <- lift $ getNode nId
_ <- case eitherInfo of
(Right node') -> void $ modifyState $ _info ?~ node'
(Left err) -> do
liftEffect $ log err
liftEffect <<< log $ "Node Corpus fetched."
performAction _ _ _ = pure unit
getNode :: Int -> Aff (Either String (NodePoly CorpusInfo))
getNode id = get $ toUrl Back Node id
_info :: Lens' State (Maybe (NodePoly CorpusInfo))
_info = lens (\s -> s.info) (\s ss -> s{info = ss})
...@@ -22,7 +22,7 @@ import Gargantext.Pages.Annuaire.User.Users as U ...@@ -22,7 +22,7 @@ import Gargantext.Pages.Annuaire.User.Users as U
import Gargantext.Pages.Home as L import Gargantext.Pages.Home as L
import Gargantext.Pages.Layout.Actions (Action(..), _corpusAction, _addCorpusAction, _docAnnotationViewAction, _docViewAction, _graphExplorerAction, _loginAction, _searchAction, _treeAction, _userPageAction, performAction, _annuaireAction) import Gargantext.Pages.Layout.Actions (Action(..), _corpusAction, _addCorpusAction, _docAnnotationViewAction, _docViewAction, _graphExplorerAction, _loginAction, _searchAction, _treeAction, _userPageAction, performAction, _annuaireAction)
import Gargantext.Pages.Layout.Specs.AddCorpus as AC import Gargantext.Pages.Layout.Specs.AddCorpus as AC
import Gargantext.Pages.Layout.Specs.Search as S import Gargantext.Pages.Layout.Specs.Search as S
import Gargantext.Pages.Layout.States (AppState, _corpusState, _addCorpusState, _docAnnotationViewState, _docViewState, _graphExplorerState, _loginState, _searchState, _treeState, _userPageState, _annuaireState) import Gargantext.Pages.Layout.States (AppState, _corpusState, _addCorpusState, _docAnnotationViewState, _docViewState, _graphExplorerState, _loginState, _searchState, _treeState, _userPageState, _annuaireState)
import Gargantext.Router (Routes(..)) import Gargantext.Router (Routes(..))
import React (ReactElement) import React (ReactElement)
......
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