Annuaire uses the Table component

parent 390aa390
......@@ -8,10 +8,9 @@ import Effect (Effect)
import Effect.Aff (Aff)
import React as React
import React (ReactElement, ReactClass, Children, createElement)
import React.DOM (a, b, b', div, option, select, span, table, tbody, td, text, th, thead, tr)
import React.DOM.Props (className, href, onChange, onClick, scope, selected, value)
import Thermite (PerformAction, Render, Spec, modifyState, simpleSpec,
createReactSpec, StateCoTransformer)
import React.DOM (a, b, b', p, i, h3, hr, div, option, select, span, table, tbody, td, text, th, thead, tr)
import React.DOM.Props (className, href, onChange, onClick, scope, selected, value, style)
import Thermite (PerformAction, Render, Spec, modifyState, simpleSpec, createReactSpec, StateCoTransformer)
import Unsafe.Coerce (unsafeCoerce)
import Gargantext.Prelude
......@@ -60,6 +59,39 @@ changePageSize ps td =
, currentPage = 1
}
-- TODO: Not sure this is the right place for this function.
renderTableHeaderLayout :: { title :: String
, desc :: String
, query :: String
, date :: String
, user :: String
} -> Array ReactElement
renderTableHeaderLayout {title, desc, query, date, user} =
[ div [className "row"]
[ div [className "col-md-3"] [ h3 [] [text 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 $ " " <> desc
]
, p [] [ i [className "fab fa-searchengin"] []
, text $ " " <> query
]
]
, div [ className "col-md-4 content"]
[ p [] [ i [className "fa fa-calendar"] []
, text $ " " <> date
]
, p [] [ i [className "fa fa-user"] []
, text $ " " <> user
]
]
]
]
]
tableSpec :: Spec State Props Action
tableSpec = simpleSpec performAction render
where
......
module Gargantext.Pages.Annuaire where
import Control.Monad.Trans.Class (lift)
import Data.Lens (Lens', lens, (?~))
import Data.Argonaut (class DecodeJson, decodeJson, (.?), (.??))
import Data.Lens (Prism', prism)
import Data.Either (Either(..))
import Data.Maybe (Maybe(..), maybe)
import React (ReactElement)
import React.DOM (a, b, b', br', div, h3, hr, i, input, p, table, tbody, td, text, th, thead, tr)
import React.DOM.Props (className, href, scope, style)
import React as React
import React (ReactClass, ReactElement)
import React.DOM (a, br', div, input, p, text)
import React.DOM.Props (href)
import Effect.Aff (Aff)
import Thermite (Render, Spec
, simpleSpec
, PerformAction, modifyState)
import Thermite ( Render, Spec
, createClass, simpleSpec, defaultPerformAction
)
------------------------------------------------------------------------------
import Gargantext.Prelude
import Gargantext.Components.Loader as Loader
import Gargantext.Components.Loader (createLoaderClass)
import Gargantext.Components.Tab as Tab
import Gargantext.Components.Table as Table
import Gargantext.Config (toUrl, NodeType(..), TabType(..), End(..))
import Gargantext.Config.REST (get)
import Gargantext.Pages.Annuaire.User.Contacts.Types (Contact(..), HyperData(..))
import Gargantext.Utils.DecodeMaybe ((.?|))
import Data.Argonaut (class DecodeJson, decodeJson, (.?))
------------------------------------------------------------------------------
type State = { info :: Maybe AnnuaireInfo
, stable :: Maybe AnnuaireTable
}
type Offset = Int
type Limit = Int
type PageSize = Int
type Props = {path :: Int, loaded :: Maybe AnnuaireInfo }
data Action = Load Int
| ChangePageSize PageSize -- TODO
| ChangePage Int -- TODO
data Action
= TabsA Tab.Action
type AnnuaireTable' = Table IndividuView
newtype Table a
= Table
{ rows :: Array { row :: a }
, totalPages :: Int
, currentPage :: Int
, pageSize :: PageSize
, totalRecords :: Int
, title :: String
}
_tabsAction :: Prism' Action Tab.Action
_tabsAction = prism TabsA \ action ->
case action of
TabsA taction -> Right taction
-- _-> Left action
newtype IndividuView
= CorpusView
......@@ -53,12 +44,16 @@ newtype IndividuView
}
------------------------------------------------------------------------------
initialState :: State
initialState = { info : Nothing, stable : Nothing }
-- unused
defaultAnnuaireTable :: AnnuaireTable
defaultAnnuaireTable = AnnuaireTable { annuaireTable : [Nothing] }
defaultAnnuaireTable = AnnuaireTable { annuaireTable : [] }
-- unused
defaultHyperdataAnnuaire :: HyperdataAnnuaire
defaultHyperdataAnnuaire = HyperdataAnnuaire { title: Nothing, desc: Nothing }
-- unused
defaultAnnuaireInfo :: AnnuaireInfo
defaultAnnuaireInfo = AnnuaireInfo { id : 0
, typename : 0
......@@ -66,83 +61,74 @@ defaultAnnuaireInfo = AnnuaireInfo { id : 0
, parentId : 0
, name : ""
, date : ""
, hyperdata : ""
, hyperdata : defaultHyperdataAnnuaire
}
------------------------------------------------------------------------------
toRows :: AnnuaireTable -> Array (Maybe Contact)
toRows (AnnuaireTable a) = a.annuaireTable
layoutAnnuaire :: Spec State {} Action
layoutAnnuaire = simpleSpec performAction render
layout :: Spec {} {annuaireId :: Int} Void
layout = simpleSpec defaultPerformAction render
where
render :: Render {} {annuaireId :: Int} Void
render _ {annuaireId} _ _ =
[ annuaireLoader
{ path: annuaireId
, component: createClass "LoadedAnnuaire" loadedAnnuaireSpec {}
} ]
loadedAnnuaireSpec :: Spec {} Props Void
loadedAnnuaireSpec = simpleSpec defaultPerformAction render
where
performAction :: PerformAction State {} Action
performAction (Load aId) _ _ = do
info' <- lift $ getInfo aId
void $ modifyState $ _info ?~ info'
table' <- lift $ getTable aId
logs "Feching Table"
void $ modifyState $ _table ?~ table'
logs "Annuaire page fetched."
performAction (ChangePageSize _) _ _ = pure unit -- TODO
performAction (ChangePage _) _ _ = pure unit -- TODO
render :: Render State {} Action
render dispatch _ state _ = [ div [className "row"]
[ div [className "col-md-3"] [ h3 [] [text info.name] ]
, 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 info.name
]
]
, div [ className "col-md-4 content"]
[ p [] [ i [className "fa fa-calendar"] []
, text ("Last update: " <> info.date)
]
]
]
]
, p [] []
, div [] [ text " Filter ", input []]
, br'
, div [className "row"]
[ div [className "col-md-1"] [b [] [text "title"]]
--, div [className "col-md-2"] [sizeDD d.pageSize dispatch]
--, div [className "col-md-3"] [textDescription d.currentPage d.pageSize d.totalRecords]
--, div [className "col-md-3"] [pagination dispatch d.totalPages d.currentPage]
]
, table [ className "table"]
[thead [ className "thead-dark"]
[tr [] [ th [scope "col"] [ b' [text ""] ]
, th [scope "col"] [ b' [text "Name"] ]
, th [scope "col"] [ b' [text "Role"] ]
, th [scope "col"] [ b' [text "Service"] ]
, th [scope "col"] [ b' [text "Company"] ]
]
]
, tbody [] $ map showRow individuals
render :: Render {} Props Void
render _ {loaded: Nothing} _ _ = []
render _ {path, loaded: Just (AnnuaireInfo {name, date})} _ _ =
Table.renderTableHeaderLayout
{ title: name
, desc: name
, query: ""
, date: "Last update: " <> date
, user: ""
} <>
[ p [] []
, div [] [ text " Filter ", input []]
, br'
, Table.tableElt
{ loadRows
, title: "title" -- TODO
, colNames:
[ ""
, "Name"
, "Role"
, "Service"
, "Company"
]
]
where
(AnnuaireInfo info) = maybe defaultAnnuaireInfo identity state.info
(AnnuaireTable stable) = maybe defaultAnnuaireTable identity state.stable
individuals = maybe (toRows defaultAnnuaireTable) toRows state.stable
showRow :: Maybe Contact -> ReactElement
showRow Nothing = tr [][]
showRow (Just (Contact { id : id, hyperdata : (HyperData contact) })) =
tr []
[ td [] [ a [ href (toUrl Front NodeUser id) ] [ text $ maybe' contact.nom <> " " <> maybe' contact.prenom ] ]
, td [] [text $ maybe' contact.fonction]
, td [] [text $ maybe' contact.service]
, td [] [text $ maybe' contact.groupe]
, totalRecords: 47361 -- TODO
}
]
where
annuaireId = path
loadRows {offset, limit} = do -- TODO use offset and limit
(AnnuaireTable {annuaireTable: rows}) <- getTable annuaireId
pure $ (\c -> {row: renderContactCells c, delete: false}) <$> rows
renderContactCells :: Contact -> Array ReactElement
renderContactCells (Contact { id, hyperdata : HyperData contact }) =
[ a [ href (toUrl Front NodeUser id) ] [ text $ maybe' contact.nom <> " " <> maybe' contact.prenom ]
, text $ maybe' contact.fonction
, text $ maybe' contact.service
, text $ maybe' contact.groupe
]
where
maybe' = maybe "" identity
where
maybe' = maybe "" identity
data HyperdataAnnuaire = HyperdataAnnuaire
{ title :: Maybe String
, desc :: Maybe String }
instance decodeHyperdataAnnuaire :: DecodeJson HyperdataAnnuaire where
decodeJson json = do
obj <- decodeJson json
title <- obj .?? "title"
desc <- obj .?? "desc"
pure $ HyperdataAnnuaire { title, desc }
------------------------------------------------------------------------------
newtype AnnuaireInfo = AnnuaireInfo { id :: Int
......@@ -151,7 +137,7 @@ newtype AnnuaireInfo = AnnuaireInfo { id :: Int
, parentId :: Int
, name :: String
, date :: String
, hyperdata :: String
, hyperdata :: HyperdataAnnuaire
}
instance decodeAnnuaireInfo :: DecodeJson AnnuaireInfo where
......@@ -174,7 +160,8 @@ instance decodeAnnuaireInfo :: DecodeJson AnnuaireInfo where
}
newtype AnnuaireTable = AnnuaireTable { annuaireTable :: Array (Maybe Contact)}
newtype AnnuaireTable = AnnuaireTable { annuaireTable :: Array Contact }
instance decodeAnnuaireTable :: DecodeJson AnnuaireTable where
decodeJson json = do
rows <- decodeJson json
......@@ -183,12 +170,12 @@ instance decodeAnnuaireTable :: DecodeJson AnnuaireTable where
getTable :: Int -> Aff AnnuaireTable
getTable id = get $ toUrl Back (Tab TabDocs 0 10) id
getInfo :: Int -> Aff AnnuaireInfo
getInfo id = get $ toUrl Back Node id
getAnnuaireInfo :: Int -> Aff AnnuaireInfo
getAnnuaireInfo id = get $ toUrl Back Node id
------------------------------------------------------------------------------
_table :: Lens' State (Maybe AnnuaireTable)
_table = lens (\s -> s.stable) (\s ss -> s{stable = ss})
_info :: Lens' State (Maybe AnnuaireInfo)
_info = lens (\s -> s.info) (\s ss -> s{info = ss})
------------------------------------------------------------------------------
annuaireLoaderClass :: ReactClass (Loader.Props Int AnnuaireInfo)
annuaireLoaderClass = createLoaderClass "AnnuaireLoader" getAnnuaireInfo
annuaireLoader :: Loader.Props Int AnnuaireInfo -> ReactElement
annuaireLoader = React.createLeafElement annuaireLoaderClass
......@@ -7,8 +7,6 @@ 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, createClass, defaultPerformAction, focus
, simpleSpec, noState )
--------------------------------------------------------
......@@ -16,6 +14,7 @@ import Gargantext.Prelude
import Gargantext.Components.Node (NodePoly(..))
import Gargantext.Components.Loader as Loader
import Gargantext.Components.Loader (createLoaderClass)
import Gargantext.Components.Table as Table
import Gargantext.Config (toUrl, NodeType(..), End(..))
import Gargantext.Config.REST (get)
import Gargantext.Pages.Corpus.Tabs.Types (CorpusInfo(..), corpusInfoDefault)
......@@ -66,36 +65,19 @@ 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"}] ]
]
, 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 $ " " <> date'
]
, p [] [ i [className "fa fa-user"] []
, text $ " " <> corpus.authors
]
]
]
]
]
where
NodePoly { name: title
, date: date'
, hyperdata : CorpusInfo corpus
}
= maybe corpusInfoDefault identity loaded
Table.renderTableHeaderLayout
{ title: "Corpus " <> title
, desc: corpus.desc
, query: corpus.query
, date: date'
, user: corpus.authors
}
where
NodePoly { name: title
, date: date'
, hyperdata : CorpusInfo corpus
}
= maybe corpusInfoDefault identity loaded
------------------------------------------------------------------------
......
......@@ -19,7 +19,7 @@ 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.Tabs.Types (CorpusInfo(..), Props)
import Gargantext.Pages.Corpus.Dashboard (globalPublis)
------------------------------------------------------------------------
-- TODO: Pagination Details are not available from the BackEnd
......@@ -103,7 +103,7 @@ instance decodeResponse :: DecodeJson Response where
-- | Filter
filterSpec :: Spec State {} Action
filterSpec :: Spec {} {} Void
filterSpec = simpleSpec defaultPerformAction render
where
render d p s c = [div [] [ text " Filter "
......@@ -111,10 +111,10 @@ filterSpec = simpleSpec defaultPerformAction render
]]
-- | Main layout of the Documents Tab of a Corpus
layoutDocview :: Spec State Props Action
layoutDocview :: Spec {} Props Void
layoutDocview = simpleSpec absurd render
where
render :: Render State Props Action
render :: Render {} Props Void
render dispatch {path, loaded} _ _ =
[ div [className "container1"]
[ div [className "row"]
......@@ -202,9 +202,6 @@ sampleData = map (\(Tuple t s) -> DocumentsView {_id : 1, url : "", date : "2017
sampleDocuments :: Array (Tuple String String)
sampleDocuments = [Tuple "Macroscopic dynamics of the fusion process" "Journal de Physique Lettres",Tuple "Effects of static and cyclic fatigue at high temperature upon reaction bonded silicon nitride" "Journal de Physique Colloques",Tuple "Reliability of metal/glass-ceramic junctions made by solid state bonding" "Journal de Physique Colloques",Tuple "High temperature mechanical properties and intergranular structure of sialons" "Journal de Physique Colloques",Tuple "SOLUTIONS OF THE LANDAU-VLASOV EQUATION IN NUCLEAR PHYSICS" "Journal de Physique Colloques",Tuple "A STUDY ON THE FUSION REACTION 139La + 12C AT 50 MeV/u WITH THE VUU EQUATION" "Journal de Physique Colloques",Tuple "Atomic structure of \"vitreous\" interfacial films in sialon" "Journal de Physique Colloques",Tuple "MICROSTRUCTURAL AND ANALYTICAL CHARACTERIZATION OF Al2O3/Al-Mg COMPOSITE INTERFACES" "Journal de Physique Colloques",Tuple "Development of oxidation resistant high temperature NbTiAl alloys and intermetallics" "Journal de Physique IV Colloque",Tuple "Determination of brazed joint constitutive law by inverse method" "Journal de Physique IV Colloque",Tuple "Two dimensional estimates from ocean SAR images" "Nonlinear Processes in Geophysics",Tuple "Comparison Between New Carbon Nanostructures Produced by Plasma with Industrial Carbon Black Grades" "Journal de Physique III",Tuple "<i>Letter to the Editor:</i> SCIPION, a new flexible ionospheric sounder in Senegal" "Annales Geophysicae",Tuple "Is reducibility in nuclear multifragmentation related to thermal scaling?" "Physics Letters B",Tuple "Independence of fragment charge distributions of the size of heavy multifragmenting sources" "Physics Letters B",Tuple "Hard photons and neutral pions as probes of hot and dense nuclear matter" "Nuclear Physics A",Tuple "Surveying the nuclear caloric curve" "Physics Letters B",Tuple "A hot expanding source in 50 A MeV Xe+Sn central reactions" "Physics Letters B"]
initialState :: State
initialState = {}
newtype SearchQuery = SearchQuery
{
query :: Array String
......
......@@ -18,7 +18,7 @@ type State =
initialState :: State
initialState =
{ docsView : D.initialState
{ docsView : {}
, authorsView : A.initialState
, sourcesView : S.initialState
, termsView : T.initialState
......
......@@ -11,7 +11,6 @@ import Gargantext.Pages.Corpus.Graph as GE
-- import Gargantext.Pages.Corpus.Tabs.Terms.NgramsTable as NG
import Gargantext.Pages.Annuaire.User.Contacts as C
import Gargantext.Pages.Annuaire as Annuaire
-- import Gargantext.Pages.Home as L
-- import Gargantext.Pages.Layout.Specs.Search as S
import Gargantext.Router (Routes(..))
......@@ -47,8 +46,7 @@ dispatchAction dispatcher _ (UserPage id) = do
dispatcher $ UserPageA $ C.FetchContact id
dispatchAction dispatcher _ (Annuaire id) = do
dispatcher $ SetRoute $ Annuaire id
dispatcher $ AnnuaireAction $ Annuaire.Load id
dispatcher $ SetRoute $ Annuaire id
dispatchAction dispatcher _ (Folder id) = do
dispatcher $ SetRoute $ Folder id
......
......@@ -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(..), _addCorpusAction, _documentViewAction, _graphExplorerAction, _loginAction, _searchAction, _treeAction, _userPageAction, performAction, _annuaireAction)
import Gargantext.Pages.Layout.Actions (Action(..), _addCorpusAction, _documentViewAction, _graphExplorerAction, _loginAction, _searchAction, _treeAction, _userPageAction, performAction)
import Gargantext.Pages.Layout.Specs.AddCorpus as AC
import Gargantext.Pages.Layout.Specs.Search as S
import Gargantext.Pages.Layout.States (AppState, _addCorpusState, _documentViewState, _graphExplorerState, _loginState, _searchState, _treeState, _userPageState, _annuaireState)
import Gargantext.Pages.Layout.States (AppState, _addCorpusState, _documentViewState, _graphExplorerState, _loginState, _searchState, _treeState, _userPageState)
import Gargantext.Router (Routes(..))
layoutSpec :: Spec AppState {} Action
......@@ -62,7 +62,7 @@ pagesComponent s = case s.currentRoute of
selectSpec PGraphExplorer = focus _graphExplorerState _graphExplorerAction GE.specOld
selectSpec Dashboard = layout0 $ noState Dsh.layoutDashboard
selectSpec (Annuaire i) = layout0 $ focus _annuaireState _annuaireAction A.layoutAnnuaire
selectSpec (Annuaire i) = layout0 $ cmapProps (const {annuaireId: i}) $ noState A.layout
selectSpec (UserPage i) = layout0 $ focus _userPageState _userPageAction C.layoutUser
-- To be removed
selectSpec NGramsTable = layout0 $ noState NG.ngramsTableSpec
......
......@@ -8,8 +8,6 @@ import Gargantext.Components.Login as LN
import Gargantext.Components.Tree as Tree
import Gargantext.Pages.Corpus.Document as D
import Gargantext.Pages.Annuaire as Annuaire
import Gargantext.Pages.Corpus.Tabs.Documents as DV
import Gargantext.Pages.Corpus.Graph as GE
import Gargantext.Pages.Annuaire.User.Contacts as C
import Gargantext.Pages.Layout.Specs.AddCorpus as AC
......@@ -20,11 +18,9 @@ type AppState =
{ currentRoute :: Maybe Routes
, loginState :: LN.State
, addCorpusState :: AC.State
, docViewState :: DV.State
, searchState :: S.State
, userPageState :: C.State
, documentState :: D.State
, annuaireState :: Annuaire.State
, ntreeState :: Tree.State
, search :: String
, showLogin :: Boolean
......@@ -38,12 +34,10 @@ initAppState =
{ currentRoute : Just Home
, loginState : LN.initialState
, addCorpusState : AC.initialState
, docViewState : DV.initialState
, searchState : S.initialState
, userPageState : C.initialState
, documentState : D.initialState
, ntreeState : Tree.exampleTree
, annuaireState : Annuaire.initialState
, search : ""
, showLogin : false
, showCorpus : false
......@@ -58,18 +52,12 @@ _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})
_docViewState :: Lens' AppState DV.State
_docViewState = lens (\s -> s.docViewState) (\s ss -> s{docViewState = ss})
_searchState :: Lens' AppState S.State
_searchState = lens (\s -> s.searchState) (\s ss -> s{searchState = ss})
_userPageState :: Lens' AppState C.State
_userPageState = lens (\s -> s.userPageState) (\s ss -> s{userPageState = ss})
_annuaireState :: Lens' AppState Annuaire.State
_annuaireState = lens (\s -> s.annuaireState) (\s ss -> s{annuaireState = ss})
_documentViewState :: Lens' AppState D.State
_documentViewState = lens (\s -> s.documentState) (\s ss -> s{documentState = ss})
......
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