Commit 7caa64fc authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

[HAL] refactoring of IMT orgs

Now they are fetched from the backend. Draft version of structId_i
also added.
parent 26cfe4ac
Pipeline #2621 failed with stage
in 0 seconds
......@@ -2,21 +2,26 @@ module Gargantext.Components.Forest.Tree.Node.Action.Search.SearchField where
import Gargantext.Prelude
import DOM.Simple.Console (log, log2)
import Data.Maybe (Maybe(..), maybe, fromMaybe)
import Data.Newtype (over)
import Data.Nullable (null)
import Data.Set as Set
import Data.String.Common (joinWith)
import DOM.Simple.Console (log, log2)
import Effect (Effect)
import Effect.Aff (launchAff_)
import Effect.Class (liftEffect)
import Gargantext.Components.Forest.Tree.Node.Action.Search.Frame (searchIframes)
import Gargantext.Components.Forest.Tree.Node.Action.Search.Types (DataField(..), Database(..), IMT_org(..), Org(..), SearchQuery(..), allIMTorgs, allOrgs, dataFields, defaultSearchQuery, doc, performSearch, datafield2database, Search)
import Gargantext.Components.Forest.Tree.Node.Action.Search.Types (DataField(..), Database(..), IMT_org(..), Org(..), SearchQuery(..), allOrgs, dataFields, defaultSearchQuery, doc, performSearch, datafield2database, Search)
import Gargantext.Components.GraphQL.Endpoints (getIMTSchools)
import Gargantext.Components.GraphQL.IMT as GQLIMT
import Gargantext.Components.InputWithEnter (inputWithEnter)
import Gargantext.Components.Lang (Lang)
import Gargantext.Components.ListSelection as ListSelection
import Gargantext.Components.ListSelection.Types as ListSelection
import Gargantext.Config.REST (logRESTError)
import Gargantext.Config.Utils (handleRESTError)
import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Sessions (Session)
import Gargantext.Types (FrontendError)
import Gargantext.Types as GT
......@@ -63,7 +68,7 @@ searchFieldCpt = here.component "searchField" cpt
-- then
-- H.div {}[]
-- else
, datafieldInput { databases, langs, search } []
, datafieldInput { databases, langs, search, session } []
, ListSelection.selection { selection, session } []
, submitButton { errors, onSearch, search, selection, session } []
]
......@@ -72,30 +77,50 @@ searchFieldCpt = here.component "searchField" cpt
type ComponentProps =
( search :: T.Box Search )
componentIMT :: R2.Component ComponentProps
componentIMT = R.createElement componentIMTCpt
componentIMTCpt :: R.Component ComponentProps
componentIMTCpt = here.component "componentIMT" cpt
where
cpt { search } _ = do
search' <- T.useLive T.unequal search
type ComponentIMTProps =
( session :: Session
| ComponentProps )
let liCpt org =
H.li {}
[ H.input { type: "checkbox"
, checked: isIn org search'.datafield
, on: { change: \_ -> ( T.modify_ (_ { datafield = updateFilter org search'.datafield }) search)
}
}
, if org == All_IMT
then H.i {} [H.text $ " " <> show org]
else H.text $ " " <> show org
]
pure $ R.fragment
[ H.ul {} $ map liCpt allIMTorgs
componentIMT :: R2.Component ComponentIMTProps
componentIMT = R.createElement componentIMTCpt
componentIMTCpt :: R.Component ComponentIMTProps
componentIMTCpt = here.component "componentIMT" cpt where
cpt { search, session } _ = do
useLoader { errorHandler
, loader: \_ -> getIMTSchools session
, path: unit
, render: \schools -> componentWithIMTOrgs { schools, search } [] }
where
errorHandler = logRESTError here "[componentIMT]"
type ComponentWithIMTOrgsProps =
( schools :: Array GQLIMT.School
, search :: T.Box Search)
componentWithIMTOrgs :: R2.Component ComponentWithIMTOrgsProps
componentWithIMTOrgs = R.createElement componentWithIMTOrgsCpt
componentWithIMTOrgsCpt :: R.Component ComponentWithIMTOrgsProps
componentWithIMTOrgsCpt = here.component "componentWithIMTOrgs" cpt where
cpt { schools, search } _ = do
search' <- T.useLive T.unequal search
let allIMTOrgs = [All_IMT] <> (IMT_org <$> schools)
liCpt org =
H.li {}
[ H.input { type: "checkbox"
, checked: isIn org search'.datafield
, on: { change: \_ -> ( T.modify_ (_ { datafield = updateFilter org allIMTOrgs search'.datafield }) search)
}
}
, case org of
All_IMT -> H.i {} [H.text $ " " <> show org]
(IMT_org { school_shortName }) -> H.text $ " " <> school_shortName
]
pure $ R.fragment
[ H.ul {} $ map liCpt $ allIMTOrgs
--, filterInput fi
]
]
componentCNRS :: R2.Component ComponentProps
componentCNRS = R.createElement componentCNRSCpt
......@@ -184,8 +209,8 @@ isIn org ( Just
) = Set.member org imtOrgs
isIn _ _ = false
updateFilter :: IMT_org -> Maybe DataField -> Maybe DataField
updateFilter org (Just (External (Just (HAL (Just (IMT imtOrgs)))))) =
updateFilter :: IMT_org -> Array IMT_org -> Maybe DataField -> Maybe DataField
updateFilter org allIMTorgs (Just (External (Just (HAL (Just (IMT imtOrgs)))))) =
(Just (External (Just (HAL (Just $ IMT imtOrgs')))))
where
imtOrgs' = if Set.member org imtOrgs
......@@ -198,7 +223,7 @@ updateFilter org (Just (External (Just (HAL (Just (IMT imtOrgs)))))) =
then Set.fromFoldable allIMTorgs
else Set.insert org imtOrgs
updateFilter org _ = (Just (External (Just (HAL (Just (IMT imtOrgs'))))))
updateFilter org allIMTorgs _ = (Just (External (Just (HAL (Just (IMT imtOrgs'))))))
where
imtOrgs' = if org == All_IMT
then Set.fromFoldable allIMTorgs
......@@ -354,13 +379,14 @@ filterInput (term /\ setTerm) =
type DatafieldInputProps =
( databases :: Array Database
, langs :: Array Lang
, search :: T.Box Search )
, search :: T.Box Search
, session :: Session )
datafieldInput :: R2.Component DatafieldInputProps
datafieldInput = R.createElement datafieldInputCpt
datafieldInputCpt :: R.Component DatafieldInputProps
datafieldInputCpt = here.component "datafieldInput" cpt where
cpt { databases, langs, search } _ = do
cpt { databases, langs, search, session} _ = do
search' <- T.useLive T.unequal search
iframeRef <- R.useRef null
......@@ -376,7 +402,7 @@ datafieldInputCpt = here.component "datafieldInput" cpt where
else H.div {} []
, if isIMT search'.datafield
then componentIMT { search } []
then componentIMT { search, session } []
else H.div {} []
, if isCNRS search'.datafield
......@@ -505,6 +531,21 @@ searchQuery :: ListSelection.Selection -> Search -> SearchQuery
searchQuery selection { datafield: Nothing, term } =
over SearchQuery (_ { query = term
, selection = selection }) defaultSearchQuery
searchQuery selection { databases, datafield: datafield@(Just (External (Just (HAL (Just (IMT imtOrgs)))))), lang, term, node_id } =
over SearchQuery (_ { databases = databases
, datafield = datafield
, lang = lang
, node_id = node_id
, query = term'
, selection = selection
}) defaultSearchQuery
where
term' = term <> " AND (" <> structIds <> ")"
joinFunc :: IMT_org -> String
joinFunc All_IMT = ""
joinFunc (IMT_org { school_id }) = "structId_i:" <> school_id
structIds :: String
structIds = joinWith " OR " $ joinFunc <$> Set.toUnfoldable imtOrgs
searchQuery selection { databases, datafield, lang, term, node_id } =
over SearchQuery (_ { databases = databases
, datafield = datafield
......
......@@ -2,7 +2,6 @@ module Gargantext.Components.Forest.Tree.Node.Action.Search.Types where
import Gargantext.Prelude
import Data.Array (concat)
import Data.Either (Either)
import Data.Generic.Rep (class Generic)
import Data.Maybe (Maybe(..), fromMaybe, maybe)
......@@ -12,6 +11,7 @@ import Data.Set as Set
import Data.String as String
import Data.Tuple (Tuple)
import Data.Tuple.Nested ((/\))
import Gargantext.Components.GraphQL.IMT as GQLIMT
import Gargantext.Components.Lang (Lang)
import Gargantext.Components.ListSelection.Types as ListSelection
import Gargantext.Config.REST (AffRESTError, RESTError)
......@@ -192,113 +192,22 @@ derive instance Eq Org
instance JSON.WriteForeign Org where writeImpl = JSON.writeImpl <<< show
------------------------------------------------------------------------
allIMTorgs :: Array IMT_org
allIMTorgs = [All_IMT] <> allIMTSubOrgs
allIMTSubOrgs :: Array IMT_org
allIMTSubOrgs = [ ARMINES
, Eurecom
, IMT_Atlantique
, IMT_Business_School
, IMT_Lille_Douai
, IMT_Mines_ALES
, IMT_Mines_Albi
, Institut_MinesTelecom_Paris
, MINES_ParisTech
, Mines_Douai
, Mines_Nantes
, Mines_SaintEtienne
, Telecom_Bretagne
, Telecom_Ecole_de_Management
, Telecom_Lille
, Telecom_ParisTech
, Telecom_SudParis
]
-- NOTE: IMT organizations are fetched via GraphQL from the backend
data IMT_org = All_IMT
| ARMINES
| Eurecom
| IMT_Atlantique
| IMT_Business_School
| IMT_Lille_Douai
| IMT_Mines_ALES
| IMT_Mines_Albi
| Institut_MinesTelecom_Paris
| MINES_ParisTech
| Mines_Douai
| Mines_Nantes
| Mines_SaintEtienne
| Telecom_Bretagne
| Telecom_Ecole_de_Management
| Telecom_Lille
| Telecom_ParisTech
| Telecom_SudParis
| IMT_org GQLIMT.School
derive instance Ord IMT_org
derive instance Eq IMT_org
instance Show IMT_org where
show All_IMT = "All_IMT"
show ARMINES = "ARMINES"
show Eurecom = "Eurecom"
show IMT_Atlantique = "IMT_Atlantique"
show IMT_Business_School = "IMT_Business_School"
show IMT_Lille_Douai = "IMT_Lille_Douai"
show IMT_Mines_ALES = "IMT_Mines_ALES"
show IMT_Mines_Albi = "IMT_Mines_Albi"
show Institut_MinesTelecom_Paris = "Institut_MinesTelecom_Paris"
show MINES_ParisTech = "MINES_ParisTech"
show Mines_Douai = "Mines_Douai"
show Mines_Nantes = "Mines_Nantes"
show Mines_SaintEtienne = "Mines_SaintEtienne"
show Telecom_Bretagne = "Telecom_Bretagne"
show Telecom_Ecole_de_Management = "Telecom_Ecole_de_Management"
show Telecom_Lille = "Telecom_Lille"
show Telecom_ParisTech = "Telecom_ParisTech"
show Telecom_SudParis = "Telecom_SudParis"
show All_IMT = "All_IMT"
show (IMT_org { school_shortName }) = school_shortName
instance Read IMT_org where
read "All_IMT" = Just All_IMT
read "ARMINES" = Just ARMINES
read "Eurecom" = Just Eurecom
read "IMT_Atlantique" = Just IMT_Atlantique
read "IMT_Business_School" = Just IMT_Business_School
read "IMT_Lille_Douai" = Just IMT_Lille_Douai
read "IMT_Mines_ALES" = Just IMT_Mines_ALES
read "IMT_Mines_Albi" = Just IMT_Mines_Albi
read "Institut_MinesTelecom_Paris" = Just Institut_MinesTelecom_Paris
read "MINES_ParisTech" = Just MINES_ParisTech
read "Mines_Douai" = Just Mines_Douai
read "Mines_Nantes" = Just Mines_Nantes
read "Mines_SaintEtienne" = Just Mines_SaintEtienne
read "Telecom_Bretagne" = Just Telecom_Bretagne
read "Telecom_Ecole_de_Management" = Just Telecom_Ecole_de_Management
read "Telecom_Lille" = Just Telecom_Lille
read "Telecom_ParisTech" = Just Telecom_ParisTech
read "Telecom_SudParis" = Just Telecom_SudParis
read _ = Nothing
imtStructId :: IMT_org -> Array StructId
imtStructId All_IMT = concat $ map imtStructId allIMTSubOrgs
imtStructId Mines_Douai = [224096]
imtStructId Telecom_Lille = [144103]
imtStructId Mines_Nantes = [84538]
imtStructId ARMINES = [300104]
imtStructId Telecom_ParisTech = [300362]
imtStructId Telecom_Bretagne = [301262]
imtStructId Telecom_Ecole_de_Management = [301442]
imtStructId MINES_ParisTech = [301492]
imtStructId Institut_MinesTelecom_Paris = [302102]
imtStructId Eurecom = [421532]
imtStructId IMT_Lille_Douai = [497330]
imtStructId Telecom_SudParis = [352124]
imtStructId IMT_Atlantique = [481355]
imtStructId IMT_Mines_Albi = [469216]
imtStructId IMT_Business_School = [542824]
imtStructId IMT_Mines_ALES = [6279]
imtStructId Mines_SaintEtienne = [29212]
------------------------------------------------------------------------
data SearchOrder
= DateAsc
......
......@@ -10,6 +10,7 @@ import Effect (Effect)
import Effect.Aff (Aff)
import Effect.Class (liftEffect)
import Foreign (unsafeToForeign, ForeignError)
import Gargantext.Components.GraphQL.IMT as GQLIMT
import Gargantext.Components.GraphQL.Node (Node)
import Gargantext.Components.GraphQL.Tree (TreeFirstLevel)
import Gargantext.Components.GraphQL.User (User, UserInfo, UserInfoM)
......@@ -68,7 +69,8 @@ queryGql session name q = do
-- Schema
type Schema
= { node_parent :: { node_id :: Int, parent_type :: String } ==> Array Node -- TODO: parent_type :: NodeType
= { imt_schools :: {} ==> Array GQLIMT.School
, node_parent :: { node_id :: Int, parent_type :: String } ==> Array Node -- TODO: parent_type :: NodeType
, user_infos :: { user_id :: Int } ==> Array UserInfo
, users :: { user_id :: Int } ==> Array User
, tree :: { root_id :: Int } ==> TreeFirstLevel
......
......@@ -12,6 +12,7 @@ import Data.Unit (unit)
import Effect.Aff (Aff)
import Effect.Class (liftEffect)
import Gargantext.Components.GraphQL (getClient, queryGql)
import Gargantext.Components.GraphQL.IMT as GQLIMT
import Gargantext.Components.GraphQL.Task as GQLT
import Gargantext.Config.REST (AffRESTError, RESTError(..))
import Gargantext.Sessions (Session)
......@@ -25,13 +26,20 @@ import Simple.JSON as JSON
here :: R2.Here
here = R2.here "Gargantext.Components.GraphQL.Endpoints"
getIMTSchools :: Session -> AffRESTError (Array GQLIMT.School)
getIMTSchools session = do
{ imt_schools } <- queryGql session "get imt schools" $
GQLIMT.schoolsQuery
liftEffect $ here.log2 "[getIMTSchools] imt_schools" imt_schools
pure $ Right imt_schools
getNodeParent :: Session -> Int -> NodeType -> Aff (Array Node)
getNodeParent session nodeId parentType = do
{ node_parent } <- queryGql session "get node parent" $
nodeParentQuery `withVars` { id: nodeId
, parent_type: show parentType } -- TODO: remove "show"
liftEffect $ here.log2 "[getNodeParent] node_parent" node_parent
pure $ node_parent
pure node_parent
getUserInfo :: Session -> Int -> AffRESTError UserInfo
getUserInfo session id = do
......
module Gargantext.Components.GraphQL.IMT where
import Gargantext.Prelude
import Affjax.RequestBody (RequestBody(..))
import Data.Array as A
import Data.Lens (Lens', lens)
import Data.Maybe (Maybe(..), fromMaybe, maybe)
import GraphQL.Client.Args (NotNull, (=>>))
import GraphQL.Client.Variable (Var(..))
type School
= { school_id :: String
, school_longName :: String
, school_shortName :: String
}
schoolsQuery = { imt_schools:
{ school_id: unit
, school_longName: unit
, school_shortName: unit}
}
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