Commit 1ecdd6fa authored by Abinaya Sudhir's avatar Abinaya Sudhir

Tabs and corpus analysis page

parent e02121a7
......@@ -82,7 +82,7 @@ performAction (LoadDatabaseDetails) _ _ = void do
cotransform $ \(state) -> state {response = resData}
performAction GO _ _ = void do
lift $ setHash "/docView"
lift $ setHash "/corpus"
modifyState id
......
module Brevets where
import Control.Monad.Eff.Console (CONSOLE)
import DOM (DOM)
import Network.HTTP.Affjax (AJAX)
import Prelude (id, void)
import Thermite (PerformAction, Render, Spec, modifyState, simpleSpec)
type State = String
initialState :: State
initialState = ""
data Action = NoOp
performAction :: forall eff props. PerformAction ( console :: CONSOLE
, ajax :: AJAX
, dom :: DOM
| eff
) State props Action
performAction NoOp _ _ = void do
modifyState id
brevetsSpec :: forall props eff . Spec ( console :: CONSOLE
, ajax :: AJAX
, dom :: DOM
| eff
) State props Action
brevetsSpec = simpleSpec performAction render
where
render :: Render State props Action
render dispatch _ state _ =
[]
module CorpusAnalysis where
import Control.Monad.Eff.Console (CONSOLE)
import DOM (DOM)
import Network.HTTP.Affjax (AJAX)
import Prelude (id, void)
import Prelude hiding (div)
import React.DOM (div, h3, hr, i, p, span, text)
import React.DOM.Props (className, style)
import Thermite (PerformAction, Render, Spec, modifyState, simpleSpec)
type State = String
initialState :: State
initialState = ""
data Action = NoOp
performAction :: forall eff props. PerformAction ( console :: CONSOLE
, ajax :: AJAX
, dom :: DOM
| eff
) State props Action
performAction NoOp _ _ = void do
modifyState id
corpusAnalysisSpec :: forall props eff . Spec ( console :: CONSOLE
, ajax :: AJAX
, dom :: DOM
| eff
) State props Action
corpusAnalysisSpec = simpleSpec performAction render
where
render :: Render State props Action
render dispatch _ state _ =
[ div [className "row"]
[ div [className "col-md-3"]
[ h3 [] [text "Bisphenol A"]
]
, div [className "col-md-9"]
[ hr [style {height : "2px",backgroundColor : "black"}] []
]
]
, div [className "row"]
[ div [className "col-md-5"]
[ div [className "jumbotron1", style {padding : "12px 0px 20px 12px"}]
[ p []
[ i [className "fa fa-globe"] []
, text "IS Tex"
]
, p []
[ i [className "fa fa-file-archive-o"] []
, text "bisphenol + A OR bpa"
]
, p []
[ i [className "fa fa-calendar"] []
, text "Sept. 11 2017, 10:59 am,"
]
, p []
[ i [className "fa fa-user"] []
, text "Authors (S): gargantext,"
]
]
]
, div [className "col-md-6"]
[]
]
]
......@@ -6,6 +6,7 @@ import Gargantext.Data.Lang
import AddCorpusview as AC
import AnnotationDocumentView as D
import Control.Monad.Eff.Console (CONSOLE)
import CorpusAnalysis as CA
import Data.Array (concat)
import Data.Either (Either(..))
import Data.Foldable (fold, intercalate)
......@@ -29,7 +30,6 @@ import Thermite (PerformAction, Render, Spec, _render, cotransform, defaultRende
import Unsafe.Coerce (unsafeCoerce)
import UserPage as UP
type E e = (dom :: DOM, ajax :: AJAX, console :: CONSOLE | e)
type AppState =
......@@ -44,6 +44,7 @@ type AppState =
, ntreeView :: NT.State
, tabview :: TV.State
, search :: String
, corpusAnalysis :: CA.State
}
initAppState :: AppState
......@@ -59,6 +60,7 @@ initAppState =
, ntreeView : NT.exampleTree
, tabview : TV.initialState
, search : ""
, corpusAnalysis : CA.initialState
}
data Action
......@@ -75,6 +77,7 @@ data Action
| TabViewA TV.Action
| Search String
| Go
| CorpusAnalysisA CA.Action
performAction :: forall eff props. PerformAction ( dom :: DOM
......@@ -196,6 +199,18 @@ _tabviewAction = prism TabViewA \action ->
_-> Left action
_corpusState :: Lens' AppState CA.State
_corpusState = lens (\s -> s.corpusAnalysis) (\s ss -> s {corpusAnalysis = ss})
_corpusAction :: Prism' Action CA.Action
_corpusAction = prism CorpusAnalysisA \action ->
case action of
CorpusAnalysisA caction -> Right caction
_-> Left action
pagesComponent :: forall props eff. AppState -> Spec (E eff) AppState props Action
pagesComponent s =
case s.currentRoute of
......@@ -209,6 +224,7 @@ pagesComponent s =
, dom :: DOM
| eff
) AppState props Action
selectSpec CorpusAnalysis = layout0 $ focus _corpusState _corpusAction CA.corpusAnalysisSpec
selectSpec Login = focus _loginState _loginAction LN.renderSpec
selectSpec Home = layout0 $ focus _landingState _landingAction (L.layoutLanding EN)
selectSpec AddCorpus = layout0 $ focus _addCorpusState _addCorpusAction AC.layoutAddcorpus
......@@ -216,9 +232,10 @@ pagesComponent s =
selectSpec UserPage = layout0 $ focus _userPageState _userPageAction UP.layoutUser
selectSpec (AnnotationDocumentView i) = layout0 $ focus _annotationdocumentviewState _annotationdocumentviewAction D.docview
selectSpec Tabview = layout0 $ focus _tabviewState _tabviewAction TV.tab1
-- To be removed
selectSpec SearchView = layout0 $ focus _searchState _searchAction S.searchSpec
selectSpec SearchView = layout0 $ focus _searchState _searchAction S.searchSpec
routingSpec :: forall props eff. Spec (dom :: DOM |eff) AppState props Action
routingSpec = simpleSpec performAction defaultRender
......@@ -537,3 +554,9 @@ dispatchAction dispatcher _ Tabview = do
_ <- dispatcher $ SetRoute $ Tabview
_ <- dispatcher $ TabViewA $ TV.NoOp
pure unit
dispatchAction dispatcher _ CorpusAnalysis = do
_ <- dispatcher $ SetRoute $ CorpusAnalysis
_ <- dispatcher $ CorpusAnalysisA $ CA.NoOp
pure unit
......@@ -24,6 +24,7 @@ data Routes
| UserPage
| AnnotationDocumentView Int
| Tabview
| CorpusAnalysis
instance showRoutes :: Show Routes where
......@@ -35,6 +36,7 @@ instance showRoutes :: Show Routes where
show UserPage = "UserPage"
show (AnnotationDocumentView i) = "DocumentView"
show Tabview = "Tabview"
show CorpusAnalysis = "corpus"
int :: Match Int
int = floor <$> num
......@@ -42,13 +44,14 @@ int = floor <$> num
routing :: Match Routes
routing =
loginRoute
loginRoute
<|> tabview
<|> documentView
<|> userPageRoute
<|> searchRoute
<|> docviewRoute
<|> addcorpusRoute
<|> corpusAnalysis
<|> home
where
tabview = Tabview <$ route "tabview"
......@@ -58,6 +61,7 @@ routing =
docviewRoute = DocView <$ route "docView"
addcorpusRoute = AddCorpus <$ route "addCorpus"
loginRoute = Login <$ route "login"
corpusAnalysis = CorpusAnalysis <$ route "corpus"
home = Home <$ lit ""
route str = lit "" *> lit str
......
module Projects where
import Control.Monad.Eff.Console (CONSOLE)
import DOM (DOM)
import Network.HTTP.Affjax (AJAX)
import Prelude (id, void)
import Thermite (PerformAction, Render, Spec, modifyState, simpleSpec)
type State = String
initialState :: State
initialState = ""
data Action = NoOp
performAction :: forall eff props. PerformAction ( console :: CONSOLE
, ajax :: AJAX
, dom :: DOM
| eff
) State props Action
performAction NoOp _ _ = void do
modifyState id
projets :: forall props eff . Spec ( console :: CONSOLE
, ajax :: AJAX
, dom :: DOM
| eff
) State props Action
projets = simpleSpec performAction render
where
render :: Render State props Action
render dispatch _ state _ =
[]
module Publications where
import Control.Monad.Eff.Console (CONSOLE)
import DOM (DOM)
import Network.HTTP.Affjax (AJAX)
import Prelude (id, void)
import React.DOM (table, tbody, td, text, th, thead, tr)
import React.DOM.Props (className, scope)
import Thermite (PerformAction, Render, Spec, modifyState, simpleSpec)
type State = String
initialState :: State
initialState = ""
data Action = NoOp
performAction :: forall eff props. PerformAction ( console :: CONSOLE
, ajax :: AJAX
, dom :: DOM
| eff
) State props Action
performAction NoOp _ _ = void do
modifyState id
publicationSpec :: forall props eff . Spec ( console :: CONSOLE
, ajax :: AJAX
, dom :: DOM
| eff
) State props Action
publicationSpec = simpleSpec performAction render
where
render :: Render State props Action
render dispatch _ state _ =
[ table [ className "table"]
[ thead [ className "thead-dark"]
[ tr []
[ th [ scope "col"] [ text "Date" ]
, th [ scope "col"] [ text "Description" ]
, th [ scope "col"] [ text "Projects" ]
, th [ scope "col"] [ text "Favorite" ]
, th [ scope "col"] [ text "Delete" ]
]
]
, tbody []
[ tr [] [ td [] [ text "2012/03/06"]
, td [] [ text "Big data and text mining"]
, td [] [ text "European funds"]
, td [] [ text "True"]
, td [] [ text "False"]
]
, tr [] [ td [] [ text "2013/03/06"]
, td [] [ text "Cryptography"]
, td [] [ text "French funds"]
, td [] [ text "True"]
, td [] [ text "False"]
]
, tr [] [ td [] [ text "2013/03/06"]
, td [] [ text "Artificial Intelligence"]
, td [] [ text "Not found"]
, td [] [ text "True"]
, td [] [ text "False"]
]
]
]
]
module UserPage where
import Tab
import Brevets as B
import Control.Monad.Eff.Console (CONSOLE)
import DOM (DOM)
import Data.Either (Either(..))
import Data.Lens (Lens', Prism', lens, prism)
import Data.List (fromFoldable)
import Data.Tuple (Tuple(..))
import DocView as DV
import Network.HTTP.Affjax (AJAX)
import Prelude hiding (div)
import Projects as PS
import Publications as P
import React.DOM (a, div, h3, h5, h6, i, img, li, nav, small, span, table, tbody, td, text, th, thead, tr, ul)
import React.DOM.Props (_data, _id, aria, className, href, role, scope, src)
import Thermite (PerformAction, Render, Spec, modifyState, simpleSpec)
import DocView as DV
import Tab as Tab
import Thermite (PerformAction, Render, Spec, focus, modifyState, simpleSpec)
type State = String
type State =
{ activeTab :: Int
, publications :: P.State
, brevets :: B.State
, projects :: PS.State
}
initialState :: State
initialState = ""
initialState =
{ activeTab : 0
, publications : P.initialState
, brevets : B.initialState
, projects : PS.initialState
}
data Action = NoOp
data Action
= NoOp
| PublicationA P.Action
| BrevetsA B.Action
| ProjectsA PS.Action
| TabA Tab.Action
performAction :: forall eff props. PerformAction ( console :: CONSOLE
, ajax :: AJAX
, dom :: DOM
| eff
) State props Action
| eff ) State props Action
performAction NoOp _ _ = void do
modifyState id
performAction _ _ _ = void do
modifyState id
layoutUser :: forall props eff . Spec ( console :: CONSOLE
, ajax :: AJAX
, dom :: DOM
......@@ -37,7 +66,7 @@ layoutUser = simpleSpec performAction render
where
render :: Render State props Action
render dispatch _ state _ =
[ -- TODO: div [className "tree"] [DV.toHtml dispatch d.tree]
[
div [className "container-fluid"]
[ div [className "row", _id "user-page-header"]
[ div [className "col-md-2"]
......@@ -97,73 +126,73 @@ layoutUser = simpleSpec performAction render
]
, div [className "row",_id "user-page-footer"]
[ div [className "col-md-12"]
facets
[]
]
]
]
facets = [ nav []
[ div [className "nav nav-tabs", _id "nav-tab",role "tablist"]
[ a [className "nav-item nav-link active",_id "nav-home-tab" , _data {toggle : "tab"},href "#nav-home" ,role "tab",aria {controls : "nav-home"} ,aria {selected:true}] [ text "Publications (12)"]
, a [className "nav-item nav-link" ,_id "nav-profile-tab", _data {toggle : "tab"},href "#nav-profile",role "tab",aria {controls : "nav-profile"},aria {selected:true}] [ text "Brevets (2)"]
, a [className "nav-item nav-link" ,_id "nav-contact-tab", _data {toggle : "tab"},href "#nav-contact",role "tab",aria {controls : "nav-contact"},aria {selected:true}] [ text "Projets (5)"]
, a [className "nav-item nav-link" ,_id "nav-contact-tab", _data {toggle : "tab"},href "#nav-contact",role "tab",aria {controls : "nav-contact"},aria {selected:true}] [ text "All (19)"]
]
]
, div [className "tab-content" , _id "nav-tabContent"]
[
div [ className "tab-pane fade show active"
, role "tabpanel"
, aria {labelledby : "nav-home-tab"}
, _id "nav-home"
]
[ facetExample ]
, div [ className "tab-pane fade show"
, role "tabpanel"
, aria {labelledby : "nav-profile-tab"}
, _id "nav-profile"
]
[ ]
, div [ className "tab-pane fade show"
, role "tabpanel"
, aria {labelledby : "nav-contact-tab"}
, _id "nav-contact"
]
[ ]
]
]
_tablens :: Lens' State Tab.State
_tablens = lens (\s -> s.activeTab) (\s ss -> s {activeTab = ss})
facetExample = table [ className "table"]
[ thead [ className "thead-dark"]
[ tr []
[ th [ scope "col"] [ text "Date" ]
, th [ scope "col"] [ text "Description" ]
, th [ scope "col"] [ text "Projects" ]
, th [ scope "col"] [ text "Favorite" ]
, th [ scope "col"] [ text "Delete" ]
]
]
, tbody []
[ tr [] [ td [] [ text "2012/03/06"]
, td [] [ text "Big data and text mining"]
, td [] [ text "European funds"]
, td [] [ text "True"]
, td [] [ text "False"]
]
, tr [] [ td [] [ text "2013/03/06"]
, td [] [ text "Cryptography"]
, td [] [ text "French funds"]
, td [] [ text "True"]
, td [] [ text "False"]
]
, tr [] [ td [] [ text "2013/03/06"]
, td [] [ text "Artificial Intelligence"]
, td [] [ text "Not found"]
, td [] [ text "True"]
, td [] [ text "False"]
]
]
]
_tabAction :: Prism' Action Tab.Action
_tabAction = prism TabA \ action ->
case action of
TabA laction -> Right laction
_-> Left action
_publens :: Lens' State P.State
_publens = lens (\s -> s.publications) (\s ss -> s { publications= ss})
_pubAction :: Prism' Action P.Action
_pubAction = prism PublicationA \ action ->
case action of
PublicationA laction -> Right laction
_-> Left action
publicationSpec :: forall eff props. Spec (dom :: DOM, console :: CONSOLE, ajax :: AJAX | eff) State props Action
publicationSpec = focus _publens _pubAction P.publicationSpec
_brevetslens :: Lens' State B.State
_brevetslens = lens (\s -> s.brevets) (\s ss -> s {brevets = ss})
_brevetsAction :: Prism' Action B.Action
_brevetsAction = prism BrevetsA \ action ->
case action of
BrevetsA laction -> Right laction
_-> Left action
brevetSpec :: forall eff props. Spec (dom :: DOM, console::CONSOLE, ajax :: AJAX | eff) State props Action
brevetSpec = focus _brevetslens _brevetsAction B.brevetsSpec
_projectslens :: Lens' State PS.State
_projectslens = lens (\s -> s.projects) (\s ss -> s {projects = ss})
_projectsAction :: Prism' Action PS.Action
_projectsAction = prism ProjectsA \ action ->
case action of
ProjectsA laction -> Right laction
_-> Left action
projectSpec :: forall eff props. Spec (dom :: DOM, console :: CONSOLE, ajax :: AJAX | eff) State props Action
projectSpec = focus _projectslens _projectsAction PS.projets
facets :: forall eff props. Spec ( dom :: DOM, console :: CONSOLE, ajax :: AJAX| eff) State props Action
facets = tabs _tablens _tabAction $ fromFoldable
[ Tuple "Publications(12)" publicationSpec
, Tuple "Brevets (2)" brevetSpec
, Tuple "Projets IMT (5)" projectSpec
]
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