Commit 113500f8 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[Annuaire Table] fix fields and adding fields to Contact.

parent 0df854d6
module Gargantext.Pages.Annuaire where
import Data.Array (head)
import Data.Argonaut (class DecodeJson, decodeJson, (.?), (.??))
import Data.Lens (Prism', prism)
import Data.Either (Either(..))
......@@ -24,7 +25,7 @@ import Gargantext.Components.Tab as Tab
import Gargantext.Components.Table as T
import Gargantext.Config (toUrl, Path(..), NodeType(..), TabType(..), End(..))
import Gargantext.Config.REST (get)
import Gargantext.Pages.Annuaire.User.Contacts.Types (Contact(..), HyperData(..), HyperdataContact(..))
import Gargantext.Pages.Annuaire.User.Contacts.Types (Contact(..), HyperData(..), HyperdataContact(..), ContactWhere(..))
------------------------------------------------------------------------------
type Props = Loader.InnerProps Int AnnuaireInfo ()
......@@ -166,16 +167,26 @@ pageLoader props = React.createElement pageLoaderClass props []
--{-
renderContactCells :: Maybe Contact -> Array ReactElement
renderContactCells Nothing = []
renderContactCells (Just (Contact { id, hyperdata : (HyperdataContact contact) })) =
renderContactCells (Just (Contact { id, hyperdata : (HyperdataContact contact@{who: who, ou:ou} ) })) =
[ text ""
, a [ href (toUrl Front NodeContact (Just id)) ] [ text $ maybe "name" identity contact.title ]
, text $ maybe "ecole" identity contact.source
, text "" -- $ maybe' contact.groupe
, text "" -- $ maybe' contact.groupe
, text $ maybe "No ContactWhere" renderContactWhereOrg (join $ head <$> ou)
, text $ maybe "No ContactWhere" renderContactWhereDept (join $ head <$> ou)
, text $ maybe "No ContactWhere" renderContactWhereRole (join $ head <$> ou)
]
where
maybe' = maybe "" identity
---}
renderContactWhereOrg (ContactWhere { organization: Nothing }) = "No Organization"
renderContactWhereOrg (ContactWhere { organization: Just orga }) =
maybe "No orga (list)" identity (head orga)
renderContactWhereDept (ContactWhere { labTeamDepts : Nothing }) = "Empty Dept"
renderContactWhereDept (ContactWhere { labTeamDepts : Just dept }) =
maybe "No Dept (list)" identity (head dept)
renderContactWhereRole (ContactWhere { role: Nothing }) = "Empty Role"
renderContactWhereRole (ContactWhere { role: Just role }) = role
data HyperdataAnnuaire = HyperdataAnnuaire
{ title :: Maybe String
......
......@@ -22,7 +22,7 @@ render dispatch _ state _ =
[
div [className "col-md-12"]
$ case state.contact of
(Just (Contact contact)) -> display (maybe "no name" identity contact.name) [contactInfos contact.hyperdata]
(Just (Contact contact)) -> display (maybe "no name" identity contact.name) (contactInfos contact.hyperdata)
Nothing -> display "Contact not found" []
]
......@@ -38,8 +38,8 @@ display title elems =
[ div [className "col-md-12"]
[ div [className "row"]
[ div [className "col-md-2"]
[ ]
-- [ img [src "/images/Gargantextuel-212x300.jpg"] ]
--[ ]
[ img [src "/images/Gargantextuel-212x300.jpg"] ]
, div [className "col-md-1"] []
, div [className "col-mdData.Unfoldable-8"] elems
]
......@@ -56,9 +56,14 @@ mapMyMap f m = toUnfoldable
infixl 4 mapMyMap as <.~$>
contactInfos :: HyperdataContact -> ReactElement
contactInfos (HyperdataContact hyperdata) =
ul [className "list-group"] (infoRender (Tuple "Name" $ maybe "no title" identity hyperdata.role)) {- $
contactInfos :: HyperdataContact -> Array ReactElement
contactInfos (HyperdataContact {who:who,ou:ou}) =
[ ul [className "list-group"] (infoRender (Tuple "Last Name" $ maybe "no title" (\(ContactWho {lastName:lastName}) -> maybe "no lastName" identity lastName) who))
, ul [className "list-group"] (infoRender (Tuple "First name" $ maybe "no title" (\(ContactWho {firstName:firstName}) -> maybe "no firstName" identity firstName) who))
]
{- $
listInfo <.~$> hyperdata
where
checkMaybe (Nothing) = empty
......
......@@ -24,26 +24,97 @@ data Contact = Contact {
, hyperdata :: HyperdataContact
}
data ContactWho =
ContactWho { idWho :: Maybe String
, firstName :: Maybe String
, lastName :: Maybe String
, keywords :: Maybe (Array String)
, freetags :: Maybe (Array String)
}
instance decodeContactWho :: DecodeJson ContactWho
where
decodeJson json = do
obj <- decodeJson json
idWho <- obj .?? "id"
firstName <- obj .?? "firstName"
lastName <- obj .?? "lastName"
keywords <- obj .?? "keywords"
freetags <- obj .?? "freetags"
pure $ ContactWho {idWho, firstName, lastName, keywords, freetags}
data ContactWhere =
ContactWhere { organization :: Maybe (Array String)
, labTeamDepts :: Maybe (Array String)
, role :: Maybe String
, office :: Maybe String
, country :: Maybe String
, city :: Maybe String
, touch :: Maybe ContactTouch
, entry :: Maybe String
, exit :: Maybe String
}
instance decodeContactWhere :: DecodeJson ContactWhere
where
decodeJson json = do
obj <- decodeJson json
organization <- obj .?? "organization"
labTeamDepts <- obj .?? "labTeamDepts"
role <- obj .?? "role"
office <- obj .?? "office"
country <- obj .?? "country"
city <- obj .?? "city"
touch <- obj .?? "touch"
entry <- obj .?? "entry"
exit <- obj .?? "exit"
pure $ ContactWhere {organization, labTeamDepts, role, office, country, city, touch, entry, exit}
data ContactTouch =
ContactTouch { mail :: Maybe String
, phone :: Maybe String
, url :: Maybe String
}
instance decodeContactTouch :: DecodeJson ContactTouch
where
decodeJson json = do
obj <- decodeJson json
mail <- obj .?? "mail"
phone <- obj .?? "phone"
url <- obj .?? "url"
pure $ ContactTouch {mail, phone, url}
data HyperdataContact =
HyperdataContact { bdd :: Maybe String
, uniqId :: Maybe String
, uniqIdBdd :: Maybe String
, who :: Maybe ContactWho
, ou :: Maybe (Array ContactWhere)
, title :: Maybe String
, source :: Maybe String
, role :: Maybe String
, lastValidation :: Maybe String
, uniqId :: Maybe String
, uniqIdBdd :: Maybe String
}
instance decodeHyperdataContact :: DecodeJson HyperdataContact
where
decodeJson json = do
obj <- decodeJson json
bdd <- obj .?? "bdd"
uniqId <- obj .?? "uniqId"
uniqIdBdd <- obj .?? "uniqIdBdd"
title <- obj .?? "title"
source <- obj .?? "source"
role <- obj .?? "role"
pure $ HyperdataContact {bdd, uniqId, uniqIdBdd, title, source, role}
bdd <- obj .?? "bdd"
who <- obj .?? "who"
ou <- obj .?? "where"
title <- obj .?? "title"
source <- obj .?? "source"
lastValidation <- obj .?? "lastValidation"
uniqId <- obj .?? "uniqId"
uniqIdBdd <- obj .?? "uniqIdBdd"
pure $ HyperdataContact {bdd, who, ou, title, source, lastValidation, uniqId, uniqIdBdd}
data HyperData c s =
......
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