Commit 88a6df4c authored by Mael NICOLAS's avatar Mael NICOLAS

working on the decodeJson instance

parent c6739d57
...@@ -3,6 +3,7 @@ module Gargantext.Pages.Annuaire where ...@@ -3,6 +3,7 @@ module Gargantext.Pages.Annuaire where
import Control.Monad.Trans.Class (lift) import Control.Monad.Trans.Class (lift)
import Data.Lens (Lens', lens, (?~)) import Data.Lens (Lens', lens, (?~))
import Data.Maybe (Maybe(..), maybe) import Data.Maybe (Maybe(..), maybe)
import Data.Map (lookup)
import React (ReactElement) import React (ReactElement)
import React.DOM (a, b, b', br', div, h3, hr, i, input, p, table, tbody, td, text, th, thead, tr) import React.DOM (a, b, b', br', div, h3, hr, i, input, p, table, tbody, td, text, th, thead, tr)
import React.DOM.Props (className, href, scope, style) import React.DOM.Props (className, href, scope, style)
...@@ -69,7 +70,7 @@ defaultAnnuaireInfo = AnnuaireInfo { id : 0 ...@@ -69,7 +70,7 @@ defaultAnnuaireInfo = AnnuaireInfo { id : 0
, hyperdata : "" , hyperdata : ""
} }
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
toRows :: AnnuaireTable -> Array (Maybe Contact) toRows :: AnnuaireTable -> Array (Maybe (Contact Void Void))
toRows (AnnuaireTable a) = a.annuaireTable toRows (AnnuaireTable a) = a.annuaireTable
layoutAnnuaire :: Spec State {} Action layoutAnnuaire :: Spec State {} Action
...@@ -131,17 +132,24 @@ layoutAnnuaire = simpleSpec performAction render ...@@ -131,17 +132,24 @@ layoutAnnuaire = simpleSpec performAction render
individuals = maybe (toRows defaultAnnuaireTable) toRows state.stable individuals = maybe (toRows defaultAnnuaireTable) toRows state.stable
showRow :: Maybe Contact -> ReactElement showRow :: Maybe (Contact Void Void) -> ReactElement
showRow Nothing = tr [][] showRow Nothing = tr [][]
showRow (Just (Contact { id : id, hyperdata : (HyperData contact) })) = showRow (Just (Contact {id: id, hyperdata: (HyperData {specific: contact}) })) =
tr [] tr []
[ td [] [ a [ href (toUrl Front NodeUser id) ] [ text $ maybe' contact.nom <> " " <> maybe' contact.prenom ] ] [ td [] [ a [ href (toUrl Front NodeUser id) ] [
, td [] [text $ maybe' contact.fonction] text $
, td [] [text $ maybe' contact.service] (maybe' $ lookInContact "prenom")
, td [] [text $ maybe' contact.groupe] <> " "
<> (maybe'$ lookInContact "nom")
]
]
, td [] [text $ maybe' $ lookInContact "fonction"]
, td [] [text $ maybe' $ lookInContact "service"]
, td [] [text $ maybe' $ lookInContact "groupe"]
] ]
where where
maybe' = maybe "" identity maybe' = maybe "" identity
lookInContact key = lookup key contact
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
...@@ -174,7 +182,7 @@ instance decodeAnnuaireInfo :: DecodeJson AnnuaireInfo where ...@@ -174,7 +182,7 @@ instance decodeAnnuaireInfo :: DecodeJson AnnuaireInfo where
} }
newtype AnnuaireTable = AnnuaireTable { annuaireTable :: Array (Maybe Contact)} newtype AnnuaireTable = AnnuaireTable { annuaireTable :: Array (Maybe (Contact Void Void))}
instance decodeAnnuaireTable :: DecodeJson AnnuaireTable where instance decodeAnnuaireTable :: DecodeJson AnnuaireTable where
decodeJson json = do decodeJson json = do
rows <- decodeJson json rows <- decodeJson json
......
...@@ -15,7 +15,7 @@ import Gargantext.Prelude ...@@ -15,7 +15,7 @@ import Gargantext.Prelude
import Gargantext.Pages.Annuaire.User.Contacts.Types (Action(..), State, Contact, _contact) import Gargantext.Pages.Annuaire.User.Contacts.Types (Action(..), State, Contact, _contact)
import Thermite (PerformAction, modifyState) import Thermite (PerformAction, modifyState)
getContact :: Int -> Aff Contact getContact :: Int -> Aff (Contact Void Void)
getContact id = get $ toUrl Back Node id getContact id = get $ toUrl Back Node id
fetchContact :: Int -> StateCoTransformer State Unit fetchContact :: Int -> StateCoTransformer State Unit
......
...@@ -4,11 +4,12 @@ module Gargantext.Pages.Annuaire.User.Contacts.Specs.Renders ...@@ -4,11 +4,12 @@ module Gargantext.Pages.Annuaire.User.Contacts.Specs.Renders
import Gargantext.Pages.Annuaire.User.Contacts.Types import Gargantext.Pages.Annuaire.User.Contacts.Types
import Data.List (List, zipWith, catMaybes, toUnfoldable) import Data.List (List, zipWith, catMaybes, toUnfoldable)
import Data.Unfoldable (class Unfoldable)
import Data.Map (Map, empty, keys, values, lookup) import Data.Map (Map, empty, keys, values, lookup)
import Data.Set (toUnfoldable) as S
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Data.Set (toUnfoldable) as S
import Data.Tuple (Tuple(..), uncurry) import Data.Tuple (Tuple(..), uncurry)
import Data.Unfoldable (class Unfoldable)
import Prelude (Void)
import Prelude (($), (<<<), (<$>), flip, class Ord) import Prelude (($), (<<<), (<$>), flip, class Ord)
import React (ReactElement) import React (ReactElement)
import React.DOM (div, h3, img, li, span, text, ul) import React.DOM (div, h3, img, li, span, text, ul)
...@@ -54,7 +55,7 @@ mapMyMap f m = toUnfoldable ...@@ -54,7 +55,7 @@ mapMyMap f m = toUnfoldable
infixl 4 mapMyMap as <.~$> infixl 4 mapMyMap as <.~$>
contactInfos :: HyperData -> ReactElement contactInfos :: HyperData Void Void -> ReactElement
contactInfos hyperdata = contactInfos hyperdata =
ul [className "list-group"] [] {- $ ul [className "list-group"] [] {- $
listInfo <.~$> hyperdata listInfo <.~$> hyperdata
......
...@@ -6,88 +6,50 @@ import Data.Argonaut (class DecodeJson, decodeJson, (.?)) ...@@ -6,88 +6,50 @@ import Data.Argonaut (class DecodeJson, decodeJson, (.?))
import Data.Either (Either(..)) import Data.Either (Either(..))
import Data.Lens (Lens', Prism', lens, prism) import Data.Lens (Lens', Prism', lens, prism)
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Data.Map (Map(..))
import React (ReactElement)
import React.DOM (div)
import Gargantext.Components.Tab as Tab import Gargantext.Components.Tab as Tab
import Gargantext.Utils.DecodeMaybe ((.?|)) import Gargantext.Utils.DecodeMaybe ((.?|))
import Gargantext.Utils.Renderable
newtype Contact = Contact data Contact c s = Contact {
{ id :: Int id :: Int
, typename :: Maybe Int , typename :: Maybe Int
, userId :: Int , userId :: Int
, parentId :: Int , parentId :: Maybe Int
, name :: String , name :: String
, date :: Maybe String , date :: Maybe String
, hyperdata :: HyperData , hyperdata :: HyperData c s
} }
newtype HyperData = data HyperData c s =
HyperData HyperData
{ bureau :: Maybe String { common :: c
, atel :: Maybe String , shared :: s
, fax :: Maybe String , specific :: Map String 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 instance decodeUserHyperData :: (DecodeJson c, DecodeJson s) =>
DecodeJson (HyperData c s) where
decodeJson json = do decodeJson json = do
obj <- decodeJson json common <- decodeJson json
bureau <- obj .?| "bureau" shared <- decodeJson json
atel <- obj .?| "atel" specific <- decodeJson json
fax <- obj .?| "fax" pure $ HyperData {common, shared, specific}
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 Contact where instance decodeUser :: (DecodeJson c, DecodeJson s) =>
DecodeJson (Contact c s) 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 $ Contact { id, typename, userId pure $ Contact { id, typename, userId
, parentId, name, date , parentId, name, date
...@@ -100,7 +62,7 @@ data Action ...@@ -100,7 +62,7 @@ data Action
type State = type State =
{ activeTab :: Int { activeTab :: Int
, contact :: Maybe Contact , contact :: Maybe (Contact )
} }
initialState :: State initialState :: State
...@@ -109,7 +71,7 @@ initialState = ...@@ -109,7 +71,7 @@ initialState =
, contact: Nothing , contact: Nothing
} }
_contact :: Lens' State (Maybe Contact) _contact :: Lens' State (Maybe (Contact Unit Unit))
_contact = lens (\s -> s.contact) (\s ss -> s{contact = ss}) _contact = lens (\s -> s.contact) (\s ss -> s{contact = ss})
_tablens :: Lens' State Tab.State _tablens :: Lens' State Tab.State
......
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