Commit 7da3fe09 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[VIEW][Corpus] only main informations.

parent fe72f3d0
module Gargantext.Pages.Corpus where
import Data.Maybe (Maybe(..), maybe)
import Prelude hiding (div)
import Data.Argonaut (class DecodeJson, decodeJson, (.?))
import Gargantext.Components.Charts.Options.ECharts (chart)
import Gargantext.Pages.Corpus.Doc.Facets.Dashboard (globalPublis)
import Gargantext.Pages.Corpus.Doc.Facets as Tab
......@@ -9,51 +10,111 @@ import React.DOM (div, h3, hr, i, p, text)
import React.DOM.Props (className, style)
import Thermite (Render, Spec, defaultPerformAction, simpleSpec)
type Corpus = { title :: String
, desc :: String
, query :: String
, date :: String
, authors :: String
}
-------------------------------------------------------------------
type State = { info :: Maybe CorpusInfo
}
initialState :: State
initialState = { info : Nothing }
data Action = Load Int
newtype Node a = Node { id :: Int
, typename :: Int
, userId :: Int
, parentId :: Int
, name :: String
, date :: String
, hyperdata :: a
}
newtype CorpusInfo = CorpusInfo { title :: String
, desc :: String
, query :: String
, date :: String
, authors :: String
, chart :: (Maybe (Array Number))
}
corpusInfoDefault :: CorpusInfo
corpusInfoDefault = CorpusInfo
{ title : "Global Publications"
, desc : " Hal Database"
, query : " Query: all publications"
, date : " June. 26 2018, 10:59 am"
, authors : " Author(s): first.last name"
, chart : Nothing
}
spec' :: Spec {} {} Void
spec' = corpusSpec <> Tab.pureTab1
instance decodeCorpusInfo :: DecodeJson CorpusInfo where
decodeJson json = do
obj <- decodeJson json
title <- obj .? "title"
desc <- obj .? "desc"
query <- obj .? "query"
date <- obj .? "date"
authors <- obj .? "authors"
chart <- obj .? "chart"
pure $ CorpusInfo {title, desc, query, date, authors, chart}
corpusSpec :: Spec {} {} Void
instance decodeNode :: (DecodeJson a) => DecodeJson (Node a) where
decodeJson json = do
obj <- decodeJson json
id <- obj .? "id"
typename <- obj .? "typename"
userId <- obj .? "userId"
parentId <- obj .? "parentId"
name <- obj .? "name"
date <- obj .? "date"
hyperdata <- obj .? "hyperdata"
hyperdata' <- decodeJson hyperdata
pure $ Node { id : id
, typename : typename
, userId : userId
, parentId : parentId
, name : name
, date : date
, hyperdata: hyperdata'
}
layout :: Spec State {} Action
layout = corpusSpec -- <> Tab.pureTab1
corpusSpec :: Spec State {} Action
corpusSpec = simpleSpec defaultPerformAction render
where
render :: Render {} {} Void
render _ _ _ _ =
[ div [className "row"]
[ div [className "col-md-3"] [ h3 [] [text corpus.title] ]
, 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 "col-md-8 content"]
[ p [] [ i [className "fa fa-globe"] []
, text corpus.desc
]
, p [] [ i [className "fab fa-searchengin"] []
, text corpus.query
]
]
, div [ className "col-md-4 content"]
[ p [] [ i [className "fa fa-calendar"] []
, text corpus.date
]
, p [] [ i [className "fa fa-user"] []
, text corpus.authors
]
]
]
render :: Render State {} Action
render dispatch _ state _ =
[ div [className "row"]
[ div [className "col-md-3"] [ h3 [] [text corpus.title] ]
, 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 "col-md-8 content"]
[ p [] [ i [className "fa fa-globe"] []
, text corpus.desc
]
, p [] [ i [className "fab fa-searchengin"] []
, text corpus.query
]
]
, div [ className "col-md-4 content"]
[ p [] [ i [className "fa fa-calendar"] []
, text corpus.date
]
, p [] [ i [className "fa fa-user"] []
, text corpus.authors
]
]
]
]
-- , chart globalPublis TODO add chart data in state
]
, chart globalPublis
]
where
corpus :: Corpus
corpus = { title : "IMT Global Publications"
, desc : " Hal Database"
, query : " Query: all publications"
, date : " June. 26 2018, 10:59 am"
, authors : " Author(s): françois.pineau"
}
where
CorpusInfo corpus = maybe corpusInfoDefault identity state.info
......@@ -7,6 +7,7 @@ import Gargantext.Pages.Layout.Specs.AddCorpus as AC
-- import Gargantext.Pages.Corpus.Doc.Facets as TV
-- import Gargantext.Pages.Corpus.Doc.Annotation as D
import Gargantext.Pages.Corpus as Corpus
import Gargantext.Pages.Corpus.Doc.Facets.Documents as DV
import Gargantext.Pages.Corpus.Doc.Facets.Graph as GE
-- import Gargantext.Pages.Corpus.Doc.Facets.Terms.NgramsTable as NG
......@@ -40,8 +41,8 @@ dispatchAction dispatcher _ (DocView n) = do
dispatcher $ DocViewA $ DV.LoadData n
dispatchAction dispatcher _ (Corpus n) = do
dispatcher $ SetRoute $ Corpus n
dispatcher $ DocViewA $ DV.LoadData n
dispatcher $ SetRoute $ Corpus n
dispatcher $ CorpusAction $ Corpus.Load n
dispatchAction dispatcher _ SearchView = do
dispatcher $ SetRoute SearchView
......
......@@ -12,6 +12,8 @@ import Effect.Console (log)
import Gargantext.Components.Login as LN
import Gargantext.Components.Modals.Modal (modalShow)
import Gargantext.Components.Tree as Tree
import Gargantext.Pages.Corpus as Corpus
import Gargantext.Pages.Corpus.Doc.Annotation as D
import Gargantext.Pages.Corpus.Doc.Facets.Documents as DV
import Gargantext.Pages.Corpus.Doc.Facets.Graph as GE
......@@ -32,12 +34,13 @@ data Action
| AddCorpusA AC.Action
| DocViewA DV.Action
| SearchA S.Action
| UserPageA U.Action
| DocAnnotationViewA D.Action
| TreeViewA Tree.Action
| GraphExplorerA GE.Action
| Search String
| TreeViewA Tree.Action
| CorpusAction Corpus.Action
| GraphExplorerA GE.Action
| DocAnnotationViewA D.Action
| AnnuaireAction Annuaire.Action
| UserPageA U.Action
| Go
| ShowLogin
| ShowAddcorpus
......@@ -96,6 +99,7 @@ performAction Initialize _ state = void do
performAction (LoginA _) _ _ = pure unit
performAction (AddCorpusA _) _ _ = pure unit
performAction (CorpusAction _) _ _ = pure unit
performAction (DocViewA _) _ _ = pure unit
performAction (SearchA _) _ _ = pure unit
performAction (UserPageA _) _ _ = pure unit
......@@ -118,6 +122,12 @@ _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
_docViewAction :: Prism' Action DV.Action
_docViewAction = prism DocViewA \action ->
case action of
......
......@@ -20,10 +20,10 @@ import Gargantext.Pages.Corpus.Doc.Facets.Graph as GE
import Gargantext.Pages.Corpus.Doc.Facets.Terms.NgramsTable as NG
import Gargantext.Pages.Annuaire.User.Users as U
import Gargantext.Pages.Home as L
import Gargantext.Pages.Layout.Actions (Action(..), _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.Search as S
import Gargantext.Pages.Layout.States (AppState, _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 React (ReactElement)
import React.DOM (a, button, div, footer, hr', img, input, li, p, span, text, ul)
......@@ -54,7 +54,7 @@ pagesComponent s =
Nothing -> selectSpec Home
where
selectSpec :: Routes -> Spec AppState {} Action
selectSpec (Corpus i) = layout0 $ focus _docViewState _docViewAction DV.layoutDocview
selectSpec (Corpus i) = layout0 $ focus _corpusState _corpusAction Corpus.layout
selectSpec Login = focus _loginState _loginAction LN.renderSpec
selectSpec Home = layout0 $ noState (L.layoutLanding EN)
selectSpec AddCorpus = layout0 $ focus _addCorpusState _addCorpusAction AC.layoutAddcorpus
......
......@@ -6,6 +6,8 @@ import Data.Lens (Lens', lens)
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.Doc.Annotation as D
import Gargantext.Pages.Annuaire as Annuaire
import Gargantext.Pages.Corpus.Doc.Facets.Documents as DV
......@@ -18,6 +20,7 @@ import Gargantext.Router (Routes(..))
type AppState =
{ currentRoute :: Maybe Routes
, loginState :: LN.State
, corpus :: Corpus.State
, addCorpusState :: AC.State
, docViewState :: DV.State
, searchState :: S.State
......@@ -35,6 +38,7 @@ type AppState =
initAppState :: AppState
initAppState =
{ currentRoute : Just Home
, corpus : Corpus.initialState
, loginState : LN.initialState
, addCorpusState : AC.initialState
, docViewState : DV.tdata
......@@ -57,6 +61,9 @@ _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})
......
......@@ -16,19 +16,41 @@ import Web.Storage.Storage (getItem)
data Routes
= Home
| Login
| AddCorpus
| DocView Int
| SearchView
| UserPage Int
| DocAnnotation Int
| Tabview
| Corpus Int
| PGraphExplorer
| NGramsTable
| Dashboard
| Annuaire Int
| Folder Int
| Folder Int
| Corpus Int
| AddCorpus
| Tabview
| DocView Int
| DocAnnotation Int
| PGraphExplorer
| NGramsTable
| Dashboard
| Annuaire Int
| UserPage Int
routing :: Match Routes
routing =
Login <$ route "login"
<|> SearchView <$ route "search"
<|> AddCorpus <$ route "addCorpus"
<|> Folder <$> (route "folder" *> int)
<|> Corpus <$> (route "corpus" *> int)
<|> Tabview <$ route "tabview"
<|> DocView <$> (route "docView" *> int)
<|> NGramsTable <$ route "ngrams"
<|> DocAnnotation <$> (route "document" *> int)
<|> Dashboard <$ route "dashboard"
<|> PGraphExplorer <$ route "graph"
<|> Annuaire <$> (route "annuaire" *> int)
<|> UserPage <$> (route "user" *> int)
<|> Home <$ lit ""
where
route str = lit "" *> lit str
int :: Match Int
int = floor <$> num
instance showRoutes :: Show Routes where
show Login = "Login"
......@@ -46,27 +68,6 @@ instance showRoutes :: Show Routes where
show PGraphExplorer = "graphExplorer"
show Home = "Home"
int :: Match Int
int = floor <$> num
routing :: Match Routes
routing =
Login <$ route "login"
<|> Tabview <$ route "tabview"
<|> DocAnnotation <$> (route "document" *> int)
<|> UserPage <$> (route "user" *> int)
<|> SearchView <$ route "search"
<|> DocView <$> (route "docView" *> int)
<|> AddCorpus <$ route "addCorpus"
<|> Corpus <$> (route "corpus" *> int)
<|> PGraphExplorer <$ route "graph"
<|> NGramsTable <$ route "ngrams"
<|> Dashboard <$ route "dashboard"
<|> Annuaire <$> (route "annuaire" *> int)
<|> Folder <$> (route "folder" *> int)
<|> Home <$ lit ""
where
route str = lit "" *> lit str
routeHandler :: (Maybe Routes -> Routes -> Effect Unit)
-> Maybe Routes -> Routes -> Effect Unit
......
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