Commit 88d50b7e authored by Alexandre Delanoë's avatar Alexandre Delanoë

Merge branch 'dev-contact' into dev

parents bee8bd29 efd8673a
...@@ -58,14 +58,14 @@ appCpt = R.hooksComponent "G.C.App.app" cpt where ...@@ -58,14 +58,14 @@ appCpt = R.hooksComponent "G.C.App.app" cpt where
case fst route of case fst route of
Home -> forested $ homeLayout EN Home -> forested $ homeLayout EN
Login -> login { sessions, backends, visible: showLogin } Login -> login { sessions, backends, visible: showLogin }
Folder sid _ -> withSession sid $ \_ -> forested (folder {}) Folder sid _ -> withSession sid $ \_ -> forested (folder {})
Corpus sid nodeId -> withSession sid $ \_ -> forested $ corpusLayout { nodeId } Corpus sid nodeId -> withSession sid $ \_ -> forested $ corpusLayout { nodeId }
Texts sid nodeId -> withSession sid $ \session -> forested $ textsLayout { nodeId, session, frontends } Texts sid nodeId -> withSession sid $ \session -> forested $ textsLayout { nodeId, session, frontends }
Lists sid nodeId -> withSession sid $ \session -> forested $ listsLayout { nodeId, session } Lists sid nodeId -> withSession sid $ \session -> forested $ listsLayout { nodeId, session }
Dashboard sid _nodeId -> withSession sid $ \session -> forested $ dashboardLayout {} Dashboard sid _nodeId -> withSession sid $ \session -> forested $ dashboardLayout {}
Annuaire sid nodeId -> withSession sid $ \session -> forested $ annuaireLayout { nodeId, session } Annuaire sid nodeId -> withSession sid $ \session -> forested $ annuaireLayout { frontends, nodeId, session }
UserPage sid nodeId -> withSession sid $ \session -> forested $ userLayout { frontends, nodeId, session } UserPage sid nodeId -> withSession sid $ \session -> forested $ userLayout { frontends, nodeId, session }
ContactPage sid nodeId -> withSession sid $ \session -> forested $ userLayout { frontends, nodeId, session } ContactPage sid _aId nodeId -> withSession sid $ \session -> forested $ userLayout { frontends, nodeId, session }
CorpusDocument sid corpusId listId nodeId -> CorpusDocument sid corpusId listId nodeId ->
withSession sid $ \session -> forested $ documentLayout { nodeId, listId, session, corpusId: Just corpusId } withSession sid $ \session -> forested $ documentLayout { nodeId, listId, session, corpusId: Just corpusId }
Document sid listId nodeId -> Document sid listId nodeId ->
......
...@@ -11,8 +11,9 @@ import Reactix as R ...@@ -11,8 +11,9 @@ import Reactix as R
import Reactix.DOM.HTML as H import Reactix.DOM.HTML as H
import Gargantext.Components.Nodes.Annuaire.User.Contacts.Types (Contact(..), HyperdataContact(..), ContactWhere(..)) import Gargantext.Components.Nodes.Annuaire.User.Contacts.Types (Contact(..), HyperdataContact(..), ContactWhere(..))
import Gargantext.Components.Table as T import Gargantext.Components.Table as T
import Gargantext.Ends (url) import Gargantext.Ends (url, Frontends)
import Gargantext.Routes (SessionRoute(..)) import Gargantext.Routes (SessionRoute(..))
import Gargantext.Routes as Routes
import Gargantext.Sessions (Session, sessionId, get) import Gargantext.Sessions (Session, sessionId, get)
import Gargantext.Types (NodePath(..), NodeType(..)) import Gargantext.Types (NodePath(..), NodeType(..))
import Gargantext.Hooks.Loader (useLoader) import Gargantext.Hooks.Loader (useLoader)
...@@ -29,7 +30,7 @@ toRows (AnnuaireTable a) = a.annuaireTable ...@@ -29,7 +30,7 @@ toRows (AnnuaireTable a) = a.annuaireTable
-- | Top level layout component. Loads an annuaire by id and renders -- | Top level layout component. Loads an annuaire by id and renders
-- | the annuaire using the result -- | the annuaire using the result
type LayoutProps = ( nodeId :: Int, session :: Session ) type LayoutProps = ( nodeId :: Int, session :: Session, frontends :: Frontends )
annuaireLayout :: Record LayoutProps -> R.Element annuaireLayout :: Record LayoutProps -> R.Element
annuaireLayout props = R.createElement annuaireLayoutCpt props [] annuaireLayout props = R.createElement annuaireLayoutCpt props []
...@@ -37,15 +38,17 @@ annuaireLayout props = R.createElement annuaireLayoutCpt props [] ...@@ -37,15 +38,17 @@ annuaireLayout props = R.createElement annuaireLayoutCpt props []
annuaireLayoutCpt :: R.Component LayoutProps annuaireLayoutCpt :: R.Component LayoutProps
annuaireLayoutCpt = R.hooksComponent "G.P.Annuaire.annuaireLayout" cpt annuaireLayoutCpt = R.hooksComponent "G.P.Annuaire.annuaireLayout" cpt
where where
cpt {nodeId, session} _ = do cpt {nodeId, session, frontends} _ = do
path <- R.useState' nodeId path <- R.useState' nodeId
useLoader (fst path) (getAnnuaireInfo session) $ useLoader (fst path) (getAnnuaireInfo session) $
\info -> annuaire {session, path, info} \info -> annuaire {session, path, info, frontends}
type AnnuaireProps = type AnnuaireProps =
( session :: Session ( session :: Session
, path :: R.State Int , path :: R.State Int
, info :: AnnuaireInfo ) , info :: AnnuaireInfo
, frontends :: Frontends
)
-- | Renders a basic table and the page loader -- | Renders a basic table and the page loader
annuaire :: Record AnnuaireProps -> R.Element annuaire :: Record AnnuaireProps -> R.Element
...@@ -55,24 +58,29 @@ annuaire props = R.createElement annuaireCpt props [] ...@@ -55,24 +58,29 @@ annuaire props = R.createElement annuaireCpt props []
annuaireCpt :: R.Component AnnuaireProps annuaireCpt :: R.Component AnnuaireProps
annuaireCpt = R.staticComponent "G.P.Annuaire.annuaire" cpt annuaireCpt = R.staticComponent "G.P.Annuaire.annuaire" cpt
where where
cpt {session, path, info: info@(AnnuaireInfo {name, date: date'})} _ = R.fragment cpt {session, path, info: info@(AnnuaireInfo {name, date: date'}), frontends} _ = R.fragment
[ T.tableHeaderLayout headerProps [ T.tableHeaderLayout headerProps
, H.p {} [] , H.p {} []
, H.div {className: "col-md-3"} , H.div {className: "col-md-3"}
[ H.text " Filter ", H.input { className: "form-control", style } ] [ H.text " Filter ", H.input { className: "form-control", style } ]
, H.br {} , H.br {}
, pageLayout { info, session, annuairePath: path } ] , pageLayout { info, session, annuairePath: path, frontends} ]
where where
headerProps = { title: name, desc: name, query: "", date, user: ""} headerProps = { title: name, desc: name, query: "", date, user: ""}
date = "Last update: " <> date' date = "Last update: " <> date'
style = {width: "250px", display: "inline-block"} style = {width: "250px", display: "inline-block"}
type PagePath = { nodeId :: Int, params :: T.Params } type PagePath = { nodeId :: Int
, params :: T.Params
, frontends :: Frontends
}
type PageLayoutProps = type PageLayoutProps =
( session :: Session ( session :: Session
, annuairePath :: R.State Int , annuairePath :: R.State Int
, info :: AnnuaireInfo ) , info :: AnnuaireInfo
, frontends :: Frontends
)
pageLayout :: Record PageLayoutProps -> R.Element pageLayout :: Record PageLayoutProps -> R.Element
pageLayout props = R.createElement pageLayoutCpt props [] pageLayout props = R.createElement pageLayoutCpt props []
...@@ -80,18 +88,19 @@ pageLayout props = R.createElement pageLayoutCpt props [] ...@@ -80,18 +88,19 @@ pageLayout props = R.createElement pageLayoutCpt props []
pageLayoutCpt :: R.Component PageLayoutProps pageLayoutCpt :: R.Component PageLayoutProps
pageLayoutCpt = R.hooksComponent "G.P.Annuaire.pageLayout" cpt pageLayoutCpt = R.hooksComponent "G.P.Annuaire.pageLayout" cpt
where where
cpt {annuairePath, info, session} _ = do cpt {annuairePath, info, session, frontends} _ = do
pagePath <- R.useState' (initialPagePath (fst annuairePath)) pagePath <- R.useState' (initialPagePath frontends (fst annuairePath))
useLoader (fst pagePath) (loadPage session) $ useLoader (fst pagePath) (loadPage session) $
\table -> page {session, table, pagePath, annuairePath} \table -> page {session, table, pagePath, annuairePath}
initialPagePath nodeId = {nodeId, params: T.initialParams} initialPagePath frontends nodeId = {nodeId, params: T.initialParams, frontends}
type PageProps = type PageProps =
( session :: Session ( session :: Session
, annuairePath :: R.State Int , annuairePath :: R.State Int
, pagePath :: R.State PagePath , pagePath :: R.State PagePath
-- , info :: AnnuaireInfo -- , info :: AnnuaireInfo
, table :: AnnuaireTable ) , table :: AnnuaireTable
)
page :: Record PageProps -> R.Element page :: Record PageProps -> R.Element
page props = R.createElement pageCpt props [] page props = R.createElement pageCpt props []
...@@ -100,26 +109,31 @@ pageCpt :: R.Component PageProps ...@@ -100,26 +109,31 @@ pageCpt :: R.Component PageProps
pageCpt = R.staticComponent "LoadedAnnuairePage" cpt pageCpt = R.staticComponent "LoadedAnnuairePage" cpt
where where
cpt { session, annuairePath, pagePath cpt { session, annuairePath, pagePath
, table: (AnnuaireTable {annuaireTable}) } _ = do , table: (AnnuaireTable {annuaireTable})} _ = do
T.table { rows, params, container, colNames, totalRecords, wrapColElts } T.table { rows, params, container, colNames, totalRecords, wrapColElts }
where where
totalRecords = 4361 -- TODO totalRecords = 4361 -- TODO
rows = (\c -> {row: contactCells session c, delete: false}) <$> annuaireTable path = fst pagePath
rows = (\c -> {row: contactCells session path.frontends path.nodeId c, delete: false}) <$> annuaireTable
container = T.defaultContainer { title: "Annuaire" } -- TODO container = T.defaultContainer { title: "Annuaire" } -- TODO
colNames = T.ColumnName <$> [ "", "Name", "Company", "Service", "Role"] colNames = T.ColumnName <$> [ "", "Name", "Company", "Service", "Role"]
wrapColElts = const identity wrapColElts = const identity
setParams f = snd pagePath $ \{nodeId, params: ps} -> setParams f = snd pagePath $ \pp@{nodeId, params: ps} ->
{params: f ps, nodeId: fst annuairePath} pp {params = f ps, nodeId = fst annuairePath}
params = T.initialParams /\ setParams params = T.initialParams /\ setParams
contactCells :: Session -> Maybe Contact -> Array R.Element type AnnuaireId = Int
contactCells session = maybe [] render
contactCells :: Session -> Frontends -> AnnuaireId -> Maybe Contact -> Array R.Element
contactCells session frontends aId = maybe [] render
where where
render (Contact { id, hyperdata : (HyperdataContact contact@{who: who, ou:ou} ) }) = render (Contact { id, hyperdata : (HyperdataContact contact@{who: who, ou:ou} ) }) =
let nodepath = NodePath (sessionId session) NodeContact (Just id) --let nodepath = NodePath (sessionId session) NodeContact (Just id)
href = url session nodepath in let nodepath = Routes.ContactPage (sessionId session) aId id
href = url frontends nodepath in
[ H.text "" [ H.text ""
, H.a { href, target: "blank" } [ H.text $ maybe "name" identity contact.title ] , H.a { href} [ H.text $ maybe "name" identity contact.title ]
--, H.a { href, target: "blank" } [ H.text $ maybe "name" identity contact.title ]
, H.text $ maybe "No ContactWhere" contactWhereOrg (head $ ou) , H.text $ maybe "No ContactWhere" contactWhereOrg (head $ ou)
, H.text $ maybe "No ContactWhere" contactWhereDept (head $ ou) , H.text $ maybe "No ContactWhere" contactWhereDept (head $ ou)
, H.div {className: "nooverflow"} , H.div {className: "nooverflow"}
......
...@@ -64,9 +64,9 @@ tabsCpt = R.hooksComponent "G.P.Annuaire.User.Contacts.Tabs.tabs" cpt ...@@ -64,9 +64,9 @@ tabsCpt = R.hooksComponent "G.P.Annuaire.User.Contacts.Tabs.tabs" cpt
] ]
where where
patentsView = {session, defaultListId, nodeId, mode: Patents} patentsView = {session, defaultListId, nodeId, mode: Patents}
booksView = {session, defaultListId, nodeId, mode: Books} booksView = {session, defaultListId, nodeId, mode: Books}
commView = {session, defaultListId, nodeId, mode: Communication} commView = {session, defaultListId, nodeId, mode: Communication}
chart = mempty chart = mempty
totalRecords = 4736 -- TODO totalRecords = 4736 -- TODO
docs = DT.docViewLayout docs = DT.docViewLayout
{ frontends, session, nodeId, chart, totalRecords { frontends, session, nodeId, chart, totalRecords
...@@ -88,4 +88,4 @@ ngramsView {session,mode, defaultListId, nodeId} = ...@@ -88,4 +88,4 @@ ngramsView {session,mode, defaultListId, nodeId} =
{ nodeId, defaultListId, tabType, session, tabNgramType } { nodeId, defaultListId, tabType, session, tabNgramType }
where where
tabNgramType = modeTabType' mode tabNgramType = modeTabType' mode
tabType = TabPairing $ TabNgramType $ modeTabType mode tabType = TabPairing $ TabNgramType $ modeTabType mode
...@@ -17,7 +17,8 @@ newtype Contact = ...@@ -17,7 +17,8 @@ newtype Contact =
, parentId :: Maybe Int , parentId :: Maybe Int
, name :: Maybe String , name :: Maybe String
, date :: Maybe String , date :: Maybe String
, hyperdata :: HyperdataContact } , hyperdata :: HyperdataContact
}
derive instance newtypeContact :: Newtype Contact _ derive instance newtypeContact :: Newtype Contact _
......
module Gargantext.Components.Nodes.Corpus where module Gargantext.Components.Nodes.Corpus where
import Prelude ((<<<)) import Prelude ((<<<))
import Data.Argonaut (class DecodeJson, decodeJson, (.:), (.??)) import Data.Argonaut (class DecodeJson, decodeJson, (.:), (.:?))
import Data.Array (head) import Data.Array (head)
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Effect.Aff (Aff, throwError) import Effect.Aff (Aff, throwError)
...@@ -24,10 +24,9 @@ corpusLayoutCpt = R.staticComponent "G.P.Corpus.corpusLayout" cpt ...@@ -24,10 +24,9 @@ corpusLayoutCpt = R.staticComponent "G.P.Corpus.corpusLayout" cpt
where where
cpt {nodeId} _ = cpt {nodeId} _ =
H.div {} H.div {}
[ H.h1 {} [H.text "Corpus Description"] [ H.iframe { src: gargMd , width: "100%", height: "100%"} []
, H.p {} [H.text "Soon: corpus synthesis here (when all others charts/features will be stabilized)."]
] ]
gargMd = "https://hackmd.iscpif.fr/g9Aah4iwQtCayIzsKQjA0Q#"
newtype CorpusInfo = newtype CorpusInfo =
CorpusInfo CorpusInfo
{ title :: String { title :: String
...@@ -65,7 +64,7 @@ instance decodeCorpusInfo :: DecodeJson CorpusInfo where ...@@ -65,7 +64,7 @@ instance decodeCorpusInfo :: DecodeJson CorpusInfo where
desc <- obj .: "desc" desc <- obj .: "desc"
query <- obj .: "query" query <- obj .: "query"
authors <- obj .: "authors" authors <- obj .: "authors"
chart <- obj .?? "chart" chart <- obj .:? "chart"
let totalRecords = 47361 -- TODO let totalRecords = 47361 -- TODO
pure $ CorpusInfo {title, desc, query, authors, chart, totalRecords} pure $ CorpusInfo {title, desc, query, authors, chart, totalRecords}
......
...@@ -17,7 +17,6 @@ import Gargantext.Components.Nodes.Corpus.Chart.Histo (histo) ...@@ -17,7 +17,6 @@ import Gargantext.Components.Nodes.Corpus.Chart.Histo (histo)
import Gargantext.Components.Tab as Tab import Gargantext.Components.Tab as Tab
import Gargantext.Components.Table as Table import Gargantext.Components.Table as Table
import Gargantext.Ends (Frontends) import Gargantext.Ends (Frontends)
import Gargantext.Routes (AppRoute)
import Gargantext.Sessions (Session) import Gargantext.Sessions (Session)
import Gargantext.Types (CTabNgramType(..), TabSubType(..), TabType(..)) import Gargantext.Types (CTabNgramType(..), TabSubType(..), TabType(..))
......
...@@ -166,6 +166,7 @@ sessionPath (R.Chart {chartType, tabType} i) = ...@@ -166,6 +166,7 @@ sessionPath (R.Chart {chartType, tabType} i) =
<> "?ngramsType=" <> showTabType' tabType <> "?ngramsType=" <> showTabType' tabType
<> "&listType=GraphTerm" -- <> show listId <> "&listType=GraphTerm" -- <> show listId
-- <> maybe "" (\x -> "&limit=" <> show x) limit -- <> maybe "" (\x -> "&limit=" <> show x) limit
-- sessionPath (R.NodeAPI (NodeContact s a i) i) = sessionPath $ "annuaire/" <> show a <> "/contact/" <> show i
------- misc routing stuff ------- misc routing stuff
......
...@@ -7,7 +7,9 @@ import Effect.Class (class MonadEffect, liftEffect) ...@@ -7,7 +7,9 @@ import Effect.Class (class MonadEffect, liftEffect)
logs:: forall message effect. logs:: forall message effect.
(MonadEffect effect) => Show message => message (MonadEffect effect)
=> Show message
=> message
-> effect Unit -> effect Unit
logs = liftEffect <<< log <<< show logs = liftEffect <<< log <<< show
...@@ -14,7 +14,7 @@ router = oneOf ...@@ -14,7 +14,7 @@ router = oneOf
, CorpusDocument <$> (route "corpus" *> sid) <*> int , CorpusDocument <$> (route "corpus" *> sid) <*> int
<*> (lit "list" *> int) <*> (lit "list" *> int)
<*> (lit "document" *> int) <*> (lit "document" *> int)
, Corpus <$> (route "corpus" *> sid) <*> int , Corpus <$> (route "corpus" *> sid) <*> int
, Document <$> (route "list" *> sid) <*> int , Document <$> (route "list" *> sid) <*> int
<*> (lit "document" *> int) <*> (lit "document" *> int)
, Dashboard <$> (route "dashboard" *> sid) <*> int , Dashboard <$> (route "dashboard" *> sid) <*> int
...@@ -23,13 +23,16 @@ router = oneOf ...@@ -23,13 +23,16 @@ router = oneOf
, Lists <$> (route "lists" *> sid) <*> int , Lists <$> (route "lists" *> sid) <*> int
, Annuaire <$> (route "annuaire" *> sid) <*> int , Annuaire <$> (route "annuaire" *> sid) <*> int
, UserPage <$> (route "user" *> sid) <*> int , UserPage <$> (route "user" *> sid) <*> int
, ContactPage <$> (route "contact" *> sid) <*> int , ContactPage <$> (route "annuaire" *> sid) <*> int
<*> (lit "contact" *> int)
, Home <$ lit "" , Home <$ lit ""
] ]
where where
route str = lit "" *> lit str route str = lit "" *> lit str
int :: Match Int int :: Match Int
int = floor <$> num int = floor <$> num
sid :: Match SessionId sid :: Match SessionId
sid = SessionId <$> str sid = SessionId <$> str
...@@ -17,7 +17,10 @@ data AppRoute ...@@ -17,7 +17,10 @@ data AppRoute
| Lists SessionId Int | Lists SessionId Int
| Annuaire SessionId Int | Annuaire SessionId Int
| UserPage SessionId Int | UserPage SessionId Int
| ContactPage SessionId Int | ContactPage SessionId AnnuaireId ContactId
type AnnuaireId = Int
type ContactId = Int
data SessionRoute data SessionRoute
= Tab TabType (Maybe Id) = Tab TabType (Maybe Id)
...@@ -38,25 +41,25 @@ instance showAppRoute :: Show AppRoute where ...@@ -38,25 +41,25 @@ instance showAppRoute :: Show AppRoute where
show (Corpus s i) = "Corpus" <> show i <> " (" <> show s <> ")" show (Corpus s i) = "Corpus" <> show i <> " (" <> show s <> ")"
show (Document _ s i) = "Document" <> show i <> " (" <> show s <> ")" show (Document _ s i) = "Document" <> show i <> " (" <> show s <> ")"
show (CorpusDocument s _ _ i) = "CorpusDocument" <> show i <> " (" <> show s <> ")" show (CorpusDocument s _ _ i) = "CorpusDocument" <> show i <> " (" <> show s <> ")"
show (PGraphExplorer s i) = "graphExplorer" <> show i <> " (" <> show s <> ")" show (PGraphExplorer s i) = "graphExplorer" <> show i <> " (" <> show s <> ")"
show (Dashboard s i) = "Dashboard" <> show i <> " (" <> show s <> ")" show (Dashboard s i) = "Dashboard" <> show i <> " (" <> show s <> ")"
show (Texts s i) = "texts" <> show i <> " (" <> show s <> ")" show (Texts s i) = "texts" <> show i <> " (" <> show s <> ")"
show (Lists s i) = "lists" <> show i <> " (" <> show s <> ")" show (Lists s i) = "lists" <> show i <> " (" <> show s <> ")"
show (Annuaire s i) = "Annuaire" <> show i <> " (" <> show s <> ")" show (Annuaire s i) = "Annuaire" <> show i <> " (" <> show s <> ")"
show (UserPage s i) = "User" <> show i <> " (" <> show s <> ")" show (UserPage s i) = "User" <> show i <> " (" <> show s <> ")"
show (ContactPage s i) = "Contact" <> show i <> " (" <> show s <> ")" show (ContactPage s _a i) = "Contact" <> show i <> " (" <> show s <> ")"
appPath :: AppRoute -> String appPath :: AppRoute -> String
appPath Home = "" appPath Home = ""
appPath Login = "login" appPath Login = "login"
appPath (Folder s i) = "folder/" <> show s <> "/" <> show i appPath (Folder s i) = "folder/" <> show s <> "/" <> show i
appPath (CorpusDocument s c l i) = "corpus/" <> show s <> "/" <> show c <> "/list/" <> show l <> "/document/" <> show i appPath (CorpusDocument s c l i) = "corpus/" <> show s <> "/" <> show c <> "/list/" <> show l <> "/document/" <> show i
appPath (Corpus s i) = "corpus/" <> show s <> "/" <> show i appPath (Corpus s i) = "corpus/" <> show s <> "/" <> show i
appPath (Document s l i) = "list/" <> show s <> "/" <> show l <> "/document/" <> show i appPath (Document s l i) = "list/" <> show s <> "/" <> show l <> "/document/" <> show i
appPath (Dashboard s i) = "dashboard/" <> show s <> "/" <> show i appPath (Dashboard s i) = "dashboard/" <> show s <> "/" <> show i
appPath (PGraphExplorer s i) = "graph/" <> show s <> "/" <> show i appPath (PGraphExplorer s i) = "graph/" <> show s <> "/" <> show i
appPath (Texts s i) = "texts/" <> show s <> "/" <> show i appPath (Texts s i) = "texts/" <> show s <> "/" <> show i
appPath (Lists s i) = "lists/" <> show s <> "/" <> show i appPath (Lists s i) = "lists/" <> show s <> "/" <> show i
appPath (Annuaire s i) = "annuaire/" <> show s <> "/" <> show i appPath (Annuaire s i) = "annuaire/" <> show s <> "/" <> show i
appPath (UserPage s i) = "user/" <> show s <> "/" <> show i appPath (UserPage s i) = "user/" <> show s <> "/" <> show i
appPath (ContactPage s i) = "contact/" <> show s <> "/" <> show i appPath (ContactPage s a i) = "annuaire/" <> show s <> "/" <> show a <> "/contact/" <> show i
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