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

[FIX] Annuaire (WIP)

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