Skip to content
Projects
Groups
Snippets
Help
Loading...
Help
Submit feedback
Contribute to GitLab
Sign in
Toggle navigation
P
purescript-gargantext
Project
Project
Details
Activity
Releases
Cycle Analytics
Repository
Repository
Files
Commits
Branches
Tags
Contributors
Graph
Compare
Charts
Issues
0
Issues
0
List
Board
Labels
Milestones
Merge Requests
0
Merge Requests
0
CI / CD
CI / CD
Pipelines
Jobs
Schedules
Charts
Wiki
Wiki
Snippets
Snippets
Members
Members
Collapse sidebar
Close sidebar
Activity
Graph
Charts
Create a new issue
Jobs
Commits
Issue Boards
Open sidebar
Grégoire Locqueville
purescript-gargantext
Commits
7da3fe09
Commit
7da3fe09
authored
Oct 09, 2018
by
Alexandre Delanoë
Browse files
Options
Browse Files
Download
Email Patches
Plain Diff
[VIEW][Corpus] only main informations.
parent
fe72f3d0
Changes
6
Show whitespace changes
Inline
Side-by-side
Showing
6 changed files
with
165 additions
and
85 deletions
+165
-85
Corpus.purs
src/Gargantext/Pages/Corpus.purs
+105
-44
Layout.purs
src/Gargantext/Pages/Layout.purs
+3
-2
Actions.purs
src/Gargantext/Pages/Layout/Actions.purs
+14
-4
Specs.purs
src/Gargantext/Pages/Layout/Specs.purs
+3
-3
States.purs
src/Gargantext/Pages/Layout/States.purs
+7
-0
Router.purs
src/Gargantext/Router.purs
+33
-32
No files found.
src/Gargantext/Pages/Corpus.purs
View file @
7da3fe09
module Gargantext.Pages.Corpus where
module Gargantext.Pages.Corpus where
import Data.Maybe (Maybe(..), maybe)
import Prelude hiding (div)
import Prelude hiding (div)
import Data.Argonaut (class DecodeJson, decodeJson, (.?))
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
...
@@ -9,21 +10,86 @@ import React.DOM (div, h3, hr, i, p, text)
...
@@ -9,21 +10,86 @@ 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, defaultPerformAction, simpleSpec)
type Corpus = { title :: 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
, desc :: String
, query :: String
, query :: String
, date :: String
, date :: String
, authors :: 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
}
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}
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'
}
}
spec' :: Spec {} {} Void
spec' = corpusSpec <> Tab.pureTab1
corpusSpec :: Spec {} {} Void
layout :: Spec State {} Action
layout = corpusSpec -- <> Tab.pureTab1
corpusSpec :: Spec State {} Action
corpusSpec = simpleSpec defaultPerformAction render
corpusSpec = simpleSpec defaultPerformAction render
where
where
render :: Render
{} {} Void
render :: Render
State {} Action
render
_ _ _
_ =
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.title] ]
, div [className "col-md-9"] [ hr [style {height : "2px",backgroundColor : "black"}] ]
, div [className "col-md-9"] [ hr [style {height : "2px",backgroundColor : "black"}] ]
...
@@ -47,13 +113,8 @@ corpusSpec = simpleSpec defaultPerformAction render
...
@@ -47,13 +113,8 @@ corpusSpec = simpleSpec defaultPerformAction render
]
]
]
]
]
]
, chart globalPublis
-- , chart globalPublis TODO add chart data in state
]
]
where
where
corpus :: Corpus
CorpusInfo corpus = maybe corpusInfoDefault identity state.info
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"
}
src/Gargantext/Pages/Layout.purs
View file @
7da3fe09
...
@@ -7,6 +7,7 @@ import Gargantext.Pages.Layout.Specs.AddCorpus as AC
...
@@ -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.Facets as TV
-- import Gargantext.Pages.Corpus.Doc.Annotation as D
-- 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.Documents as DV
import Gargantext.Pages.Corpus.Doc.Facets.Graph as GE
import Gargantext.Pages.Corpus.Doc.Facets.Graph as GE
-- import Gargantext.Pages.Corpus.Doc.Facets.Terms.NgramsTable as NG
-- import Gargantext.Pages.Corpus.Doc.Facets.Terms.NgramsTable as NG
...
@@ -41,7 +42,7 @@ dispatchAction dispatcher _ (DocView n) = do
...
@@ -41,7 +42,7 @@ dispatchAction dispatcher _ (DocView n) = do
dispatchAction dispatcher _ (Corpus n) = do
dispatchAction dispatcher _ (Corpus n) = do
dispatcher $ SetRoute $ Corpus n
dispatcher $ SetRoute $ Corpus n
dispatcher $
DocViewA $ DV.LoadData
n
dispatcher $
CorpusAction $ Corpus.Load
n
dispatchAction dispatcher _ SearchView = do
dispatchAction dispatcher _ SearchView = do
dispatcher $ SetRoute SearchView
dispatcher $ SetRoute SearchView
...
...
src/Gargantext/Pages/Layout/Actions.purs
View file @
7da3fe09
...
@@ -12,6 +12,8 @@ import Effect.Console (log)
...
@@ -12,6 +12,8 @@ import Effect.Console (log)
import Gargantext.Components.Login as LN
import Gargantext.Components.Login as LN
import Gargantext.Components.Modals.Modal (modalShow)
import Gargantext.Components.Modals.Modal (modalShow)
import Gargantext.Components.Tree as Tree
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.Annotation as D
import Gargantext.Pages.Corpus.Doc.Facets.Documents as DV
import Gargantext.Pages.Corpus.Doc.Facets.Documents as DV
import Gargantext.Pages.Corpus.Doc.Facets.Graph as GE
import Gargantext.Pages.Corpus.Doc.Facets.Graph as GE
...
@@ -32,12 +34,13 @@ data Action
...
@@ -32,12 +34,13 @@ data Action
| AddCorpusA AC.Action
| AddCorpusA AC.Action
| DocViewA DV.Action
| DocViewA DV.Action
| SearchA S.Action
| SearchA S.Action
| UserPageA U.Action
| Search String
| DocAnnotationViewA D.Action
| TreeViewA Tree.Action
| TreeViewA Tree.Action
| CorpusAction Corpus.Action
| GraphExplorerA GE.Action
| GraphExplorerA GE.Action
|
Search String
|
DocAnnotationViewA D.Action
| AnnuaireAction Annuaire.Action
| AnnuaireAction Annuaire.Action
| UserPageA U.Action
| Go
| Go
| ShowLogin
| ShowLogin
| ShowAddcorpus
| ShowAddcorpus
...
@@ -96,6 +99,7 @@ performAction Initialize _ state = void do
...
@@ -96,6 +99,7 @@ performAction Initialize _ state = void do
performAction (LoginA _) _ _ = pure unit
performAction (LoginA _) _ _ = pure unit
performAction (AddCorpusA _) _ _ = pure unit
performAction (AddCorpusA _) _ _ = pure unit
performAction (CorpusAction _) _ _ = pure unit
performAction (DocViewA _) _ _ = pure unit
performAction (DocViewA _) _ _ = pure unit
performAction (SearchA _) _ _ = pure unit
performAction (SearchA _) _ _ = pure unit
performAction (UserPageA _) _ _ = pure unit
performAction (UserPageA _) _ _ = pure unit
...
@@ -118,6 +122,12 @@ _addCorpusAction = prism AddCorpusA \action ->
...
@@ -118,6 +122,12 @@ _addCorpusAction = prism AddCorpusA \action ->
AddCorpusA caction -> Right caction
AddCorpusA caction -> Right caction
_-> Left action
_-> 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' Action DV.Action
_docViewAction = prism DocViewA \action ->
_docViewAction = prism DocViewA \action ->
case action of
case action of
...
...
src/Gargantext/Pages/Layout/Specs.purs
View file @
7da3fe09
...
@@ -20,10 +20,10 @@ import Gargantext.Pages.Corpus.Doc.Facets.Graph as GE
...
@@ -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.Corpus.Doc.Facets.Terms.NgramsTable as NG
import Gargantext.Pages.Annuaire.User.Users as U
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(..), _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, _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)
import React.DOM (a, button, div, footer, hr', img, input, li, p, span, text, ul)
import React.DOM (a, button, div, footer, hr', img, input, li, p, span, text, ul)
...
@@ -54,7 +54,7 @@ pagesComponent s =
...
@@ -54,7 +54,7 @@ pagesComponent s =
Nothing -> selectSpec Home
Nothing -> selectSpec Home
where
where
selectSpec :: Routes -> Spec AppState {} Action
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 Login = focus _loginState _loginAction LN.renderSpec
selectSpec Home = layout0 $ noState (L.layoutLanding EN)
selectSpec Home = layout0 $ noState (L.layoutLanding EN)
selectSpec AddCorpus = layout0 $ focus _addCorpusState _addCorpusAction AC.layoutAddcorpus
selectSpec AddCorpus = layout0 $ focus _addCorpusState _addCorpusAction AC.layoutAddcorpus
...
...
src/Gargantext/Pages/Layout/States.purs
View file @
7da3fe09
...
@@ -6,6 +6,8 @@ import Data.Lens (Lens', lens)
...
@@ -6,6 +6,8 @@ import Data.Lens (Lens', lens)
import Data.Maybe (Maybe(Just))
import Data.Maybe (Maybe(Just))
import Gargantext.Components.Login as LN
import Gargantext.Components.Login as LN
import Gargantext.Components.Tree as Tree
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.Annotation as D
import Gargantext.Pages.Annuaire as Annuaire
import Gargantext.Pages.Annuaire as Annuaire
import Gargantext.Pages.Corpus.Doc.Facets.Documents as DV
import Gargantext.Pages.Corpus.Doc.Facets.Documents as DV
...
@@ -18,6 +20,7 @@ import Gargantext.Router (Routes(..))
...
@@ -18,6 +20,7 @@ import Gargantext.Router (Routes(..))
type AppState =
type AppState =
{ currentRoute :: Maybe Routes
{ currentRoute :: Maybe Routes
, loginState :: LN.State
, loginState :: LN.State
, corpus :: Corpus.State
, addCorpusState :: AC.State
, addCorpusState :: AC.State
, docViewState :: DV.State
, docViewState :: DV.State
, searchState :: S.State
, searchState :: S.State
...
@@ -35,6 +38,7 @@ type AppState =
...
@@ -35,6 +38,7 @@ type AppState =
initAppState :: AppState
initAppState :: AppState
initAppState =
initAppState =
{ currentRoute : Just Home
{ currentRoute : Just Home
, corpus : Corpus.initialState
, loginState : LN.initialState
, loginState : LN.initialState
, addCorpusState : AC.initialState
, addCorpusState : AC.initialState
, docViewState : DV.tdata
, docViewState : DV.tdata
...
@@ -57,6 +61,9 @@ _loginState = lens (\s -> s.loginState) (\s ss -> s{loginState = ss})
...
@@ -57,6 +61,9 @@ _loginState = lens (\s -> s.loginState) (\s ss -> s{loginState = ss})
_addCorpusState :: Lens' AppState AC.State
_addCorpusState :: Lens' AppState AC.State
_addCorpusState = lens (\s -> s.addCorpusState) (\s ss -> s{addCorpusState = ss})
_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' AppState DV.State
_docViewState = lens (\s -> s.docViewState) (\s ss -> s{docViewState = ss})
_docViewState = lens (\s -> s.docViewState) (\s ss -> s{docViewState = ss})
...
...
src/Gargantext/Router.purs
View file @
7da3fe09
...
@@ -16,19 +16,41 @@ import Web.Storage.Storage (getItem)
...
@@ -16,19 +16,41 @@ import Web.Storage.Storage (getItem)
data Routes
data Routes
= Home
= Home
| Login
| Login
| SearchView
| Folder Int
| Corpus Int
| AddCorpus
| AddCorpus
| Tabview
| DocView Int
| DocView Int
| SearchView
| UserPage Int
| DocAnnotation Int
| DocAnnotation Int
| Tabview
| Corpus Int
| PGraphExplorer
| PGraphExplorer
| NGramsTable
| NGramsTable
| Dashboard
| Dashboard
| Annuaire Int
| Annuaire Int
| Folder
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
instance showRoutes :: Show Routes where
show Login = "Login"
show Login = "Login"
...
@@ -46,27 +68,6 @@ instance showRoutes :: Show Routes where
...
@@ -46,27 +68,6 @@ instance showRoutes :: Show Routes where
show PGraphExplorer = "graphExplorer"
show PGraphExplorer = "graphExplorer"
show Home = "Home"
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)
routeHandler :: (Maybe Routes -> Routes -> Effect Unit)
-> Maybe Routes -> Routes -> Effect Unit
-> Maybe Routes -> Routes -> Effect Unit
...
...
Write
Preview
Markdown
is supported
0%
Try again
or
attach a new file
Attach a file
Cancel
You are about to add
0
people
to the discussion. Proceed with caution.
Finish editing this message first!
Cancel
Please
register
or
sign in
to comment