Commit 00098c86 authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

[GraphQL] user fetched via the user_info endpoint

parent 2dab4e56
Pipeline #2036 failed with stage
...@@ -6,7 +6,7 @@ import Data.List.Types (NonEmptyList) ...@@ -6,7 +6,7 @@ import Data.List.Types (NonEmptyList)
import Effect.Aff (Aff) import Effect.Aff (Aff)
import Effect.Class (liftEffect) import Effect.Class (liftEffect)
import Foreign (unsafeToForeign, ForeignError) import Foreign (unsafeToForeign, ForeignError)
import Gargantext.Components.GraphQL.User (User) import Gargantext.Components.GraphQL.User (User, UserInfo)
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
import GraphQL.Client.Args (type (==>)) import GraphQL.Client.Args (type (==>))
...@@ -53,5 +53,6 @@ queryGql name q = do ...@@ -53,5 +53,6 @@ queryGql name q = do
-- Schema -- Schema
type Schema type Schema
= { users :: { user_id :: Int } ==> Array User = { user_infos :: { user_id :: Int } ==> Array UserInfo
, users :: { user_id :: Int } ==> Array User
} }
module Gargantext.Components.GraphQL.User where module Gargantext.Components.GraphQL.User where
import Data.Maybe (Maybe(..), maybe) import Data.Array as A
import Data.Lens (Lens', lens)
import Data.Maybe (Maybe(..), fromMaybe, maybe)
import Gargantext.Prelude import Gargantext.Prelude
import Type.Proxy (Proxy(..)) import Type.Proxy (Proxy(..))
type UserInfo
= { ui_id :: Int
, ui_username :: String
, ui_email :: String
, ui_title :: Maybe String
, ui_source :: Maybe String
, ui_cwFirstName :: Maybe String
, ui_cwLastName :: Maybe String
, ui_cwOrganization :: Array String
, ui_cwLabTeamDepts :: Array String
, ui_cwOffice :: Maybe String
, ui_cwCity :: Maybe String
, ui_cwCountry :: Maybe String
, ui_cwRole :: Maybe String
, ui_cwTouchPhone :: Maybe String
, ui_cwTouchMail :: Maybe String }
_ui_cwFirstName :: Lens' UserInfo String
_ui_cwFirstName = lens getter setter
where
getter ({ ui_cwFirstName: val }) = fromMaybe "" val
setter ui val = ui { ui_cwFirstName = Just val }
_ui_cwLastName :: Lens' UserInfo String
_ui_cwLastName = lens getter setter
where
getter ({ ui_cwLastName: val }) = fromMaybe "" val
setter ui val = ui { ui_cwLastName = Just val }
_ui_cwCity :: Lens' UserInfo String
_ui_cwCity = lens getter setter
where
getter ({ ui_cwCity: val }) = fromMaybe "" val
setter ui val = ui { ui_cwCity = Just val }
_ui_cwCountry :: Lens' UserInfo String
_ui_cwCountry = lens getter setter
where
getter ({ ui_cwCountry: val }) = fromMaybe "" val
setter ui val = ui { ui_cwCountry = Just val }
_ui_cwLabTeamDepts :: Lens' UserInfo (Array String)
_ui_cwLabTeamDepts = lens getter setter
where
getter ({ ui_cwLabTeamDepts: val }) = val
setter ui val = ui { ui_cwLabTeamDepts = val }
_ui_cwLabTeamDeptsFirst :: Lens' UserInfo String
_ui_cwLabTeamDeptsFirst = lens getter setter
where
getter ({ ui_cwLabTeamDepts: val }) = fromMaybe "" $ A.head val
setter ui val = ui { ui_cwLabTeamDepts = fromMaybe [val] $ A.updateAt 0 val ui.ui_cwLabTeamDepts }
_ui_cwOffice :: Lens' UserInfo String
_ui_cwOffice = lens getter setter
where
getter ({ ui_cwOffice: val }) = fromMaybe "" val
setter ui val = ui { ui_cwOffice = Just val }
_ui_cwOrganization :: Lens' UserInfo (Array String)
_ui_cwOrganization = lens getter setter
where
getter ({ ui_cwOrganization: val }) = val
setter ui val = ui { ui_cwOrganization = val }
_ui_cwOrganizationFirst :: Lens' UserInfo String
_ui_cwOrganizationFirst = lens getter setter
where
getter ({ ui_cwOrganization: val }) = fromMaybe "" $ A.head val
setter ui val = ui { ui_cwOrganization = fromMaybe [val] $ A.updateAt 0 val ui.ui_cwOrganization }
_ui_cwRole :: Lens' UserInfo String
_ui_cwRole = lens getter setter
where
getter ({ ui_cwRole: val }) = fromMaybe "" val
setter ui val = ui { ui_cwRole = Just val }
_ui_cwTouchMail :: Lens' UserInfo String
_ui_cwTouchMail = lens getter setter
where
getter ({ ui_cwTouchMail: val }) = fromMaybe "" val
setter ui val = ui { ui_cwTouchMail = Just val }
_ui_cwTouchPhone :: Lens' UserInfo String
_ui_cwTouchPhone = lens getter setter
where
getter ({ ui_cwTouchPhone: val }) = fromMaybe "" val
setter ui val = ui { ui_cwTouchPhone = Just val }
type User type User
= { u_id :: Int = { u_id :: Int
, u_hyperdata :: , u_hyperdata ::
{ _hu_shared :: Maybe { shared :: Maybe
{ _hc_title :: Maybe String { title :: Maybe String
, _hc_source :: Maybe String , source :: Maybe String
, _hc_who :: Maybe , who :: Maybe
{ _cw_firstName :: Maybe String { firstName :: Maybe String
, _cw_lastName :: Maybe String , lastName :: Maybe String
} }
, _hc_where :: Array , "where" :: Array
{ _cw_organization :: Array String } { organization :: Array String }
} }
} }
, u_username :: String , u_username :: String
...@@ -28,28 +108,33 @@ showUser { u_id ...@@ -28,28 +108,33 @@ showUser { u_id
showMUser u = maybe "" showUser u showMUser u = maybe "" showUser u
-- Symbols -- Symbols
u_id :: Proxy "u_id" ui_id :: Proxy "ui_id"
u_id = Proxy ui_id = Proxy
u_hyperdata :: Proxy "u_hyperdata" ui_username :: Proxy "ui_username"
u_hyperdata = Proxy ui_username = Proxy
u_username :: Proxy "u_username" ui_email :: Proxy "ui_email"
u_username = Proxy ui_email = Proxy
u_email :: Proxy "u_email" ui_title :: Proxy "ui_title"
u_email = Proxy ui_title = Proxy
ui_source :: Proxy "ui_source"
_hu_shared :: Proxy "shared" ui_source = Proxy
_hu_shared = Proxy ui_cwFirstName :: Proxy "ui_cwFirstName"
_hc_source :: Proxy "_hc_source" ui_cwFirstName = Proxy
_hc_source = Proxy ui_cwLastName :: Proxy "ui_cwLastName"
_hc_title :: Proxy "_hc_title" ui_cwLastName = Proxy
_hc_title = Proxy ui_cwCity :: Proxy "ui_cwCity"
_hc_who :: Proxy "_hc_who" ui_cwCity = Proxy
_hc_who = Proxy ui_cwCountry :: Proxy "ui_cwCountry"
_hc_where :: Proxy "_cw_where" ui_cwCountry = Proxy
_hc_where = Proxy ui_cwLabTeamDepts :: Proxy "ui_cwLabTeamDepts"
_cw_firstName :: Proxy "_cw_firstName" ui_cwLabTeamDepts = Proxy
_cw_firstName = Proxy ui_cwOrganization :: Proxy "ui_cwOrganization"
_cw_lastName :: Proxy "_cw_lastName" ui_cwOrganization = Proxy
_cw_lastName = Proxy ui_cwOffice :: Proxy "ui_cwOffice"
_cw_organization :: Proxy "_cw_organization" ui_cwOffice = Proxy
_cw_organization = Proxy ui_cwRole :: Proxy "ui_cwRole"
ui_cwRole = Proxy
ui_cwTouchMail :: Proxy "ui_cwTouchMail"
ui_cwTouchMail = Proxy
ui_cwTouchPhone :: Proxy "ui_cwTouchPhone"
ui_cwTouchPhone = Proxy
...@@ -11,6 +11,7 @@ import Effect.Aff (Aff) ...@@ -11,6 +11,7 @@ import Effect.Aff (Aff)
import Gargantext.Components.App.Data (Boxes) import Gargantext.Components.App.Data (Boxes)
import Gargantext.Components.DocsTable as DT import Gargantext.Components.DocsTable as DT
import Gargantext.Components.DocsTable.Types (Year) import Gargantext.Components.DocsTable.Types (Year)
import Gargantext.Components.GraphQL.User (UserInfo)
import Gargantext.Components.NgramsTable as NT import Gargantext.Components.NgramsTable as NT
import Gargantext.Components.NgramsTable.Core as NTC import Gargantext.Components.NgramsTable.Core as NTC
import Gargantext.Components.Nodes.Annuaire.User.Contacts.Types (ContactData) import Gargantext.Components.Nodes.Annuaire.User.Contacts.Types (ContactData)
...@@ -50,13 +51,13 @@ modeTabType' Books = CTabAuthors ...@@ -50,13 +51,13 @@ modeTabType' Books = CTabAuthors
modeTabType' Communication = CTabAuthors modeTabType' Communication = CTabAuthors
type TabsProps = type TabsProps =
( boxes :: Boxes ( boxes :: Boxes
, cacheState :: T.Box LTypes.CacheState , cacheState :: T.Box LTypes.CacheState
, contactData :: ContactData , defaultListId :: Int
, frontends :: Frontends , frontends :: Frontends
, nodeId :: Int , nodeId :: Int
, session :: Session , session :: Session
, sidePanel :: T.Box (Maybe (Record TextsT.SidePanel)) , sidePanel :: T.Box (Maybe (Record TextsT.SidePanel))
) )
tabs :: R2.Leaf TabsProps tabs :: R2.Leaf TabsProps
...@@ -68,21 +69,21 @@ tabsCpt = here.component "tabs" cpt where ...@@ -68,21 +69,21 @@ tabsCpt = here.component "tabs" cpt where
yearFilter <- T.useBox (Nothing :: Maybe Year) yearFilter <- T.useBox (Nothing :: Maybe Year)
pure $ Tab.tabs { activeTab, tabs: tabs' yearFilter props } pure $ Tab.tabs { activeTab, tabs: tabs' yearFilter props }
tabs' yearFilter props@{ boxes, sidePanel } = tabs' yearFilter props@{ boxes, defaultListId, sidePanel } =
[ "Documents" /\ docs [ "Documents" /\ docs
, "Patents" /\ ngramsView (viewProps Patents) , "Patents" /\ ngramsView (viewProps Patents)
, "Books" /\ ngramsView (viewProps Books) , "Books" /\ ngramsView (viewProps Books)
, "Communication" /\ ngramsView (viewProps Communication) , "Communication" /\ ngramsView (viewProps Communication)
, "Trash" /\ docs -- TODO pass-in trash mode , "Trash" /\ docs -- TODO pass-in trash mode
] where ] where
viewProps mode = Record.merge props { defaultListId: props.contactData.defaultListId viewProps mode = Record.merge props { mode }
, mode } totalRecords = 4736 -- TODO lol
totalRecords = 4736 -- TODO lol
docs = DT.docViewLayout (Record.merge { boxes, sidePanel } $ Record.merge dtCommon dtExtra) docs = DT.docViewLayout (Record.merge { boxes, sidePanel } $ Record.merge dtCommon dtExtra)
dtCommon = RX.pick props :: Record DTCommon dtCommon = RX.pick props :: Record DTCommon
dtExtra = dtExtra =
{ chart: mempty { chart: mempty
, listId: props.contactData.defaultListId --, listId: props.contactData.defaultListId
, listId: defaultListId
, mCorpusId: Nothing , mCorpusId: Nothing
, showSearch: true , showSearch: true
, tabType: TabPairing TabDocs , tabType: TabPairing TabDocs
...@@ -100,8 +101,7 @@ type DTCommon = ...@@ -100,8 +101,7 @@ type DTCommon =
) )
type NgramsViewTabsProps = type NgramsViewTabsProps =
( defaultListId :: Int ( mode :: Mode
, mode :: Mode
| TabsProps ) | TabsProps )
ngramsView :: R2.Leaf NgramsViewTabsProps ngramsView :: R2.Leaf NgramsViewTabsProps
......
...@@ -47,14 +47,14 @@ modeTabType' Patents = CTabAuthors ...@@ -47,14 +47,14 @@ modeTabType' Patents = CTabAuthors
modeTabType' Books = CTabAuthors modeTabType' Books = CTabAuthors
modeTabType' Communication = CTabAuthors modeTabType' Communication = CTabAuthors
type TabsProps = ( type TabsProps =
boxes :: Boxes ( boxes :: Boxes
, cacheState :: T.Box LTypes.CacheState , cacheState :: T.Box LTypes.CacheState
, contactData :: ContactData' , defaultListId :: Int
, frontends :: Frontends , frontends :: Frontends
, nodeId :: Int , nodeId :: Int
, session :: Session , session :: Session
, sidePanel :: T.Box (Maybe (Record TTypes.SidePanel)) , sidePanel :: T.Box (Maybe (Record TTypes.SidePanel))
) )
tabs :: R2.Leaf TabsProps tabs :: R2.Leaf TabsProps
...@@ -64,7 +64,7 @@ tabsCpt = here.component "tabs" cpt ...@@ -64,7 +64,7 @@ tabsCpt = here.component "tabs" cpt
where where
cpt { boxes cpt { boxes
, cacheState , cacheState
, contactData: {defaultListId} , defaultListId
, frontends , frontends
, nodeId , nodeId
, session , session
...@@ -134,7 +134,6 @@ type NgramsViewTabsProps = ( ...@@ -134,7 +134,6 @@ type NgramsViewTabsProps = (
ngramsView :: R2.Component NgramsViewTabsProps ngramsView :: R2.Component NgramsViewTabsProps
ngramsView = R.createElement ngramsViewCpt ngramsView = R.createElement ngramsViewCpt
ngramsViewCpt :: R.Component NgramsViewTabsProps ngramsViewCpt :: R.Component NgramsViewTabsProps
ngramsViewCpt = here.component "ngramsView" cpt ngramsViewCpt = here.component "ngramsView" cpt
where where
......
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