Commit 25c62883 authored by Mael NICOLAS's avatar Mael NICOLAS

it works ! Need to get the id from the url and change some css :,(

parent 70425023
'use strict';
exports.isNull = function(v) {
return v === null;
};
module DecodeMaybe where
import Prelude
import Data.Argonaut (class DecodeJson, JObject, getFieldOptional)
import Data.Either (Either)
import Data.Maybe (Maybe(..))
foreign import isNull :: forall a. a -> Boolean
getFieldOptional' :: forall a. DecodeJson a => JObject -> String -> Either String (Maybe a)
getFieldOptional' o s = (case _ of
Just v -> if isNull v then Nothing else v
Nothing -> Nothing
) <$> (getFieldOptional o s)
infix 7 getFieldOptional' as .?|
......@@ -12,12 +12,12 @@ import Data.Lens (set)
import Data.Maybe (Maybe(..))
import Gargantext.REST (get)
import Network.HTTP.Affjax (AJAX)
import Prelude (bind, id, pure, show, void, ($), (<<<), (<>))
import Prelude (bind, id, show, void, ($), (<<<), (<>))
import Thermite (PerformAction, modifyState)
getUser :: forall eff. Int -> Aff
(console :: CONSOLE, ajax :: AJAX | eff) (Either String User)
getUser id = get $ "localhost:8008/node/" <> show id
getUser id = get $ "http://localhost:8008/node/" <> show id
performAction :: forall eff props. PerformAction ( console :: CONSOLE
......@@ -30,7 +30,9 @@ performAction (FetchUser userId) _ _ = void do
value <- lift $ getUser userId
_ <- case value of
(Right user) -> modifyState \state -> set _user (Just user) state
_ -> modifyState id
pure <<< log $ "Fetching user..."
(Left err) -> do
_ <- lift $ log err
modifyState id
lift <<< log $ "Fetching user..."
performAction _ _ _ = void do
modifyState id
......@@ -3,10 +3,6 @@ module Gargantext.Users.Specs.Renders
import Gargantext.Users.Types
import Control.Monad.Aff (attempt)
import Control.Monad.Aff.Class (liftAff)
import Data.Either (Either(..))
import Data.Generic (gShow)
import Data.Maybe (Maybe(..))
import Data.Tuple (Tuple(..))
import Prelude (($), (<<<))
......@@ -41,18 +37,20 @@ card title elems =
]
]
userInfos :: ReactElement
userInfos =
userInfos :: HyperData -> ReactElement
userInfos (HyperData user) =
ul [className "list-group"]
[
listElement <<< infoRender $ Tuple "Fonction: " "Enseignant chercheur"
, listElement <<< infoRender $ Tuple "Entité, service: " "Mines Saint-Etienne SPIN -PTSI"
, listElement <<< infoRender $ Tuple "Téléphone: " "(+33) 4 77 42 00 70"
, listElement <<< infoRender $ Tuple "Courriel: " "gargantua@rabelais.fr"
, listElement <<< infoRender $ Tuple "Bureau: " "D1/10"
, listElement <<< infoRender $ Tuple "Appelation: " "Maître de conférences (EPA)"
, listElement <<< infoRender $ Tuple "Lieu: " "Saint-Etienne, 158 Cours Fauriel"
listElement <<< infoRender <<< Tuple "Fonction: " $ checkMaybe user.fonction
, listElement <<< infoRender <<< Tuple "Entité, service: " $ checkMaybe user.entite
, listElement <<< infoRender <<< Tuple "Téléphone: " $ checkMaybe user.atel
, listElement <<< infoRender <<< Tuple "Courriel: " $ checkMaybe user.mail
, listElement <<< infoRender <<< Tuple "Bureau: " $ checkMaybe user.bureau
, listElement <<< infoRender <<< Tuple "Appelation: " $ checkMaybe user.fonction
, listElement <<< infoRender $ Tuple "Lieu: " $ checkMaybe user.lieu
]
where checkMaybe (Nothing) = ""
checkMaybe (Just a) = a
pbInfos :: ReactElement
pbInfos =
......@@ -74,9 +72,9 @@ render dispatch _ state _ =
[
button [RP.onClick \_ -> dispatch $ FetchUser 452145] [ text "Fetch User"],
div [className "col-md-8"]
$ card (case state.user of (Just _) -> "Ok"
Nothing -> "Pas Ok")
[userInfos]
$ case state.user of
(Just (User user)) -> card user.name [userInfos user.hyperdata]
Nothing -> card "Aucun utilisateur" []
]
]
]
......
module Gargantext.Users.Types.Types where
import Data.Argonaut (class DecodeJson, decodeJson, (.?))
import Data.Generic (class Generic)
import Data.Maybe (Maybe)
import Prelude (bind, pure, ($))
import DecodeMaybe
newtype User =
User {
id :: Int,
typename :: Int,
userId :: Int,
id ::Int,
typename :: Maybe Int,
userId ::Int,
parentId :: Int,
name :: String,
date :: String,
hyperData :: HyperData
date ::Maybe String,
hyperdata :: HyperData
}
newtype HyperData =
HyperData
{
bureau :: String,
atel :: String,
fax :: String,
aprecision :: String,
service :: String,
service2 :: String,
groupe :: String,
lieu :: String,
pservice :: String,
date_modification :: String,
fonction :: String,
pfonction :: String,
url :: String,
prenom :: String,
nom :: String,
idutilentite :: String,
afonction :: String,
grprech :: String,
entite :: String,
entite2 :: String
bureau ::Maybe String,
atel ::Maybe String,
fax ::Maybe String,
aprecision ::Maybe String,
service ::Maybe String,
service2 ::Maybe String,
groupe ::Maybe String,
lieu ::Maybe String,
pservice ::Maybe String,
date_modification ::Maybe String,
fonction ::Maybe String,
pfonction ::Maybe String,
url ::Maybe String,
prenom ::Maybe String,
nom ::Maybe String,
idutilentite ::Maybe String,
afonction ::Maybe String,
grprech ::Maybe String,
entite ::Maybe String,
entite2 ::Maybe String,
mail :: Maybe String
}
instance decodeUserHyperData :: DecodeJson HyperData where
decodeJson json = do
obj <- decodeJson json
bureau <- obj .? "bureau"
atel <- obj .? "atel"
fax <- obj .? "fax"
aprecision <- obj .? "aprecision"
service <- obj .? "service"
service2 <- obj .? "service2"
groupe <- obj .? "groupe"
lieu <- obj .? "lieu"
pservice <- obj .? "pservice"
date_modification <- obj .? "date_modification"
fonction <- obj .? "fonction"
pfonction <- obj .? "pfonction"
url <- obj .? "url"
prenom <- obj .? "prenom"
nom <- obj .? "nom"
idutilentite <- obj .? "idutilentite"
afonction <- obj .? "afonction"
grprech <- obj .? "grprech"
entite <- obj .? "entite"
entite2 <- obj .? "entite2"
pure $ HyperData {bureau, atel, fax, aprecision, service, service2, groupe, lieu, pservice, date_modification, fonction, pfonction, url, prenom, nom, idutilentite, afonction, grprech, entite, entite2}
bureau <- obj .?| "bureau"
atel <- obj .?| "atel"
fax <- obj .?| "fax"
aprecision <- obj .?| "aprecision"
service <- obj .?| "service"
service2 <- obj .?| "service2"
groupe <- obj .?| "groupe"
lieu <- obj .?| "lieu"
pservice <- obj .?| "pservice"
date_modification <- obj .?| "date_modification"
fonction <- obj .?| "fonction"
pfonction <- obj .?| "pfonction"
url <- obj .?| "url"
prenom <- obj .?| "prenom"
nom <- obj .?| "nom"
idutilentite <- obj .?| "idutilentite"
afonction <- obj .?| "afonction"
grprech <- obj .?| "grprech"
entite <- obj .?| "entite"
entite2 <- obj .?| "entite2"
mail <- obj .?| "mail"
pure $ HyperData {bureau, atel, fax, aprecision, service, service2, groupe, lieu, pservice, date_modification, fonction, pfonction, url, prenom, nom, idutilentite, afonction, grprech, entite, entite2, mail}
instance decodeUser :: DecodeJson User where
decodeJson json = do
obj <- decodeJson json
id <- obj .? "id"
typename <- obj .? "typename"
typename <- obj .?| "typename"
userId <- obj .? "userId"
parentId <- obj .? "parentId"
name <- obj .? "name"
date <- obj .? "date"
hyperData <- obj .? "hyperData"
pure $ User {id, typename, userId, parentId, name, date, hyperData}
date <- obj .?| "date"
hyperdata <- obj .? "hyperdata"
pure $ User {id, typename, userId, parentId, name, date, hyperdata}
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