Commit 5a95a885 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[FIX] Annuaire (WIP)

parent 858d1150
module Gargantext.Components.Nodes.Annuaire where
import Prelude (bind, const, identity, pure, ($), (<$>), (<>))
import Data.Argonaut (class DecodeJson, decodeJson, (.:), (.:?))
import Data.Array as A
import Data.List as L
......@@ -8,17 +7,17 @@ import Data.Maybe (Maybe(..), maybe, fromMaybe)
import Data.Tuple (fst, snd)
import Data.Tuple.Nested ((/\))
import Effect.Aff (Aff)
import Reactix as R
import Reactix.DOM.HTML as H
import Gargantext.Components.Nodes.Annuaire.User.Contacts.Types as CT
import Gargantext.Components.Table as T
import Gargantext.Ends (url, Frontends)
import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Routes (SessionRoute(..))
import Gargantext.Routes as Routes
import Gargantext.Sessions (Session, sessionId, get)
import Gargantext.Types (NodeType(..), AffTableResult, TableResult)
import Gargantext.Hooks.Loader (useLoader)
import Prelude (bind, const, identity, pure, ($), (<$>), (<>))
import Reactix as R
import Reactix.DOM.HTML as H
newtype IndividuView =
CorpusView
......@@ -102,7 +101,7 @@ type PageProps =
, frontends :: Frontends
, pagePath :: R.State PagePath
-- , info :: AnnuaireInfo
, table :: TableResult CT.Contact
, table :: TableResult CT.NodeContact
)
page :: Record PageProps -> R.Element
......@@ -123,7 +122,7 @@ pageCpt = R.hooksComponent "LoadedAnnuairePage" cpt
, session }
, delete: false }) <$> L.fromFoldable docs
container = T.defaultContainer { title: "Annuaire" } -- TODO
colNames = T.ColumnName <$> [ "", "Name", "Company", "Service", "Role"]
colNames = T.ColumnName <$> [ "", "First Name", "Last Name", "Company", "Lab", "Role"]
wrapColElts = const identity
setParams f = snd pagePath $ \pp@{params: ps} ->
pp {params = f ps}
......@@ -132,9 +131,8 @@ pageCpt = R.hooksComponent "LoadedAnnuairePage" cpt
type AnnuaireId = Int
type ContactCellsProps =
(
annuaireId :: AnnuaireId
, contact :: CT.Contact
( annuaireId :: AnnuaireId
, contact :: CT.NodeContact
, frontends :: Frontends
, session :: Session
)
......@@ -146,11 +144,11 @@ contactCellsCpt :: R.Component ContactCellsProps
contactCellsCpt = R.hooksComponent "G.C.N.A.contactCells" cpt
where
cpt { annuaireId
, contact: (CT.Contact { id, hyperdata: (CT.HyperdataUser {shared: Nothing}) })
, contact: (CT.NodeContact { id, hyperdata: (CT.HyperdataContact {who : Nothing}) })
, frontends
, session } _ =
pure $ T.makeRow [ H.text ""
, H.span {} [ H.text "name" ]
, H.span {} [ H.text "Name" ]
--, H.a { href, target: "blank" } [ H.text $ fromMaybe "name" contact.title ]
, H.text "No ContactWhere"
, H.text "No ContactWhereDept"
......@@ -158,25 +156,29 @@ contactCellsCpt = R.hooksComponent "G.C.N.A.contactCells" cpt
[ H.text "No ContactWhereRole" ]
]
cpt { annuaireId
, contact: (CT.Contact { id
, hyperdata: (CT.HyperdataUser {shared: Just (CT.HyperdataContact contact@{who, ou})}) })
, contact: (CT.NodeContact { id
, hyperdata: ( CT.HyperdataContact { who : Just (CT.ContactWho { firstName
, lastName
}
)
}
)
}
)
, frontends
, session } _ = do
let
contactWho = fromMaybe CT.defaultContactWho who
CT.ContactWho {firstName} = contactWho
pure $ T.makeRow [
H.text ""
, H.text $ fromMaybe "First Name" firstName
, H.text $ fromMaybe "First Name" lastName
, H.text "CNRS"
-- , H.a { href } [ H.text $ fromMaybe "name" contact.title ]
--, H.a { href, target: "blank" } [ H.text $ fromMaybe "name" contact.title ]
--, H.text $ maybe "No ContactWhere" contactWhereOrg (A.head $ ou)
, H.text $ maybe "No ContactWhereDept" contactWhereDept (A.head $ ou)
, H.div {className: "nooverflow"} [
H.text $ maybe "No ContactWhereRole" contactWhereRole (A.head $ ou)
]
-- , H.text $ maybe "No ContactWhereDept" contactWhereDept (A.head $ ou)
-- , H.div {className: "nooverflow"} [
-- H.text $ maybe "No ContactWhereRole" contactWhereRole (A.head $ ou)
]
where
--nodepath = NodePath (sessionId session) NodeContact (Just id)
......@@ -243,7 +245,7 @@ instance decodeAnnuaireInfo :: DecodeJson AnnuaireInfo where
------------------------------------------------------------------------
loadPage :: Session -> PagePath -> AffTableResult CT.Contact
loadPage :: Session -> PagePath -> AffTableResult CT.NodeContact
loadPage session {nodeId, params: { offset, limit, orderBy }} =
get session children
-- TODO orderBy
......
......@@ -4,26 +4,25 @@ module Gargantext.Components.Nodes.Annuaire.User.Contacts
, userLayout )
where
import DOM.Simple.Console (log2)
import Data.Lens as L
import Data.Maybe (Maybe(..), fromMaybe)
import Data.Tuple (Tuple(..), fst, snd)
import Data.Tuple.Nested ((/\))
import DOM.Simple.Console (log2)
import Effect (Effect)
import Effect.Class (liftEffect)
import Effect.Aff (Aff, launchAff_)
import Reactix as R
import Reactix.DOM.HTML as H
import Gargantext.Prelude (Unit, bind, const, discard, pure, show, unit, ($), (+), (<$>), (<<<), (<>), (==))
import Gargantext.Components.Nodes.Annuaire.User.Contacts.Types (Contact(..), ContactData, ContactTouch(..), ContactWhere(..), ContactWho(..), HyperdataContact(..), HyperdataUser(..), _city, _country, _firstName, _labTeamDeptsJoinComma, _lastName, _mail, _office, _organizationJoinComma, _ouFirst, _phone, _role, _shared, _touch, _who, defaultContactTouch, defaultContactWhere, defaultContactWho, defaultHyperdataContact, defaultHyperdataUser)
import Effect.Class (liftEffect)
import Gargantext.Components.Nodes.Annuaire.User.Contacts.Tabs as Tabs
import Gargantext.Components.Nodes.Annuaire.User.Contacts.Types (Contact(..), ContactData, ContactTouch(..), ContactWhere(..), ContactWho(..), HyperdataContact(..), HyperdataUser(..), _city, _country, _firstName, _labTeamDeptsJoinComma, _lastName, _mail, _office, _organizationJoinComma, _ouFirst, _phone, _role, _shared, _touch, _who, defaultContactTouch, defaultContactWhere, defaultContactWho, defaultHyperdataContact, defaultHyperdataUser)
import Gargantext.Ends (Frontends)
import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Prelude (Unit, bind, const, discard, pure, show, unit, ($), (+), (<$>), (<<<), (<>), (==))
import Gargantext.Routes as Routes
import Gargantext.Ends (Frontends)
import Gargantext.Sessions (Session, get, put)
import Gargantext.Types (NodeType(..))
import Gargantext.Utils.Reactix as R2
import Reactix as R
import Reactix.DOM.HTML as H
display :: String -> Array R.Element -> R.Element
display title elems =
......@@ -68,8 +67,7 @@ contactInfoItems =
type HyperdataUserLens = L.ALens' HyperdataUser String
type ContactInfoItemProps =
(
hyperdata :: HyperdataUser
( hyperdata :: HyperdataUser
, label :: String
, lens :: HyperdataUserLens
, onUpdateHyperdata :: HyperdataUser -> Effect Unit
......
module Gargantext.Components.Nodes.Annuaire.User.Contacts.Types where
import Prelude
import Data.Argonaut (class DecodeJson, class EncodeJson, decodeJson, encodeJson, (.:), (.:!), (.:?), (:=), (~>), jsonEmptyObject)
import Prelude (bind, pure, ($))
import Data.Argonaut (class DecodeJson, class EncodeJson, decodeJson, (.:), (.:!), (.:?), (:=), (~>), jsonEmptyObject)
import Data.Array as A
import Data.Lens
import Data.Maybe (Maybe(..), fromMaybe)
import Data.Map (Map)
import Data.String as S
import Data.Tuple (Tuple(..))
import Gargantext.Utils.DecodeMaybe ((.?|))
import Data.Newtype (class Newtype)
-- TODO: should it be a NodePoly HyperdataContact ?
newtype NodeContact =
NodeContact
{ id :: Int
, date :: Maybe String
, hyperdata :: HyperdataContact
, name :: Maybe String
, parentId :: Maybe Int
, typename :: Maybe Int
, userId :: Maybe Int
}
instance decodeNodeContact :: DecodeJson NodeContact where
decodeJson json = do
obj <- decodeJson json
date <- obj .?| "date"
hyperdata <- obj .: "hyperdata"
id <- obj .: "id"
name <- obj .:! "name"
parentId <- obj .?| "parentId"
typename <- obj .?| "typename"
userId <- obj .:! "userId"
pure $ NodeContact { id
, date
, hyperdata
, name
, parentId
, typename
, userId
}
derive instance newtypeNodeContact :: Newtype NodeContact _
newtype Contact =
Contact
{ id :: Int
......@@ -24,6 +56,8 @@ newtype Contact =
, userId :: Maybe Int
}
instance decodeUser :: DecodeJson Contact where
decodeJson json = do
obj <- decodeJson json
......@@ -35,8 +69,7 @@ instance decodeUser :: DecodeJson Contact where
typename <- obj .?| "typename"
userId <- obj .:! "userId"
pure $ Contact {
id
pure $ Contact { id
, date
, hyperdata
, name
......@@ -215,7 +248,7 @@ instance decodeHyperdataContact :: DecodeJson HyperdataContact
title <- obj .:? "title"
uniqId <- obj .:? "uniqId"
uniqIdBdd <- obj .:? "uniqIdBdd"
who <- obj .:? "who"
who <- obj .:! "who"
let ou' = fromMaybe [] ou
......@@ -236,8 +269,7 @@ instance encodeHyperdataContact :: EncodeJson HyperdataContact
defaultHyperdataContact :: HyperdataContact
defaultHyperdataContact =
HyperdataContact {
bdd: Nothing
HyperdataContact { bdd: Nothing
, who: Nothing
, ou: []
, title: Nothing
......@@ -247,7 +279,6 @@ defaultHyperdataContact =
, uniqIdBdd: Nothing
}
newtype HyperdataUser =
HyperdataUser {
shared :: Maybe HyperdataContact
......
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