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