[search] implement per-user api key for pubmed search

parent 823a1866
...@@ -3,6 +3,7 @@ module Gargantext.Components.Forest.Tree.Node.Action.Search.SearchField where ...@@ -3,6 +3,7 @@ module Gargantext.Components.Forest.Tree.Node.Action.Search.SearchField where
import Gargantext.Prelude import Gargantext.Prelude
import Data.Array as A import Data.Array as A
import Data.Either (Either(..))
import Data.Maybe (Maybe(..), maybe, fromMaybe) import Data.Maybe (Maybe(..), maybe, fromMaybe)
import Data.Newtype (over) import Data.Newtype (over)
import Data.Nullable (null) import Data.Nullable (null)
...@@ -15,8 +16,8 @@ import Effect (Effect) ...@@ -15,8 +16,8 @@ import Effect (Effect)
import Effect.Aff (launchAff_) import Effect.Aff (launchAff_)
import Effect.Class (liftEffect) import Effect.Class (liftEffect)
import Gargantext.Components.Forest.Tree.Node.Action.Search.Frame (searchIframes) 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(..), 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, dbFromInputValue, dbToInputValue)
import Gargantext.Components.GraphQL.Endpoints (getIMTSchools) import Gargantext.Components.GraphQL.Endpoints (getIMTSchools, getNodeCorpus)
import Gargantext.Components.GraphQL.IMT as GQLIMT import Gargantext.Components.GraphQL.IMT as GQLIMT
import Gargantext.Components.InputWithEnter (inputWithEnter) import Gargantext.Components.InputWithEnter (inputWithEnter)
import Gargantext.Components.Lang (Lang(..)) import Gargantext.Components.Lang (Lang(..))
...@@ -37,13 +38,13 @@ here :: R2.Here ...@@ -37,13 +38,13 @@ here :: R2.Here
here = R2.here "Gargantext.Components.Forest.Tree.Node.Action.Search.SearchField" here = R2.here "Gargantext.Components.Forest.Tree.Node.Action.Search.SearchField"
defaultSearch :: Search defaultSearch :: Search
defaultSearch = { databases: Empty defaultSearch = { databases : Empty
, datafield: Nothing , datafield : Nothing
, node_id : Nothing , node_id : Nothing
, lang : Nothing , lang : Nothing
, term : "" , term : ""
, url : "" , url : ""
, years : [] , years : []
} }
type Props = type Props =
...@@ -93,8 +94,8 @@ componentYearsCpt = here.component "componentYears" cpt where ...@@ -93,8 +94,8 @@ componentYearsCpt = here.component "componentYears" cpt where
((yearCpt search <$> yearsZ) <> ((yearCpt search <$> yearsZ) <>
[ H.div {} [ H.div {}
[ H.input { on: { blur: modify newYear [ H.input { on: { blur: modify newYear
, change: modify newYear , change: modify newYear
, input: modify newYear } } , input: modify newYear } }
, H.span { className: "btn btn-primary fa fa-check" , H.span { className: "btn btn-primary fa fa-check"
, on: { click: clickAdd newYear search }} [] , on: { click: clickAdd newYear search }} []
] ]
...@@ -180,28 +181,19 @@ isExternal _ = false ...@@ -180,28 +181,19 @@ isExternal _ = false
isArxiv :: Maybe DataField -> Boolean isArxiv :: Maybe DataField -> Boolean
isArxiv (Just isArxiv (Just
( External ( External Arxiv )
( Just Arxiv ) = true
)
)
) = true
isArxiv _ = false isArxiv _ = false
isHAL :: Maybe DataField -> Boolean isHAL :: Maybe DataField -> Boolean
isHAL (Just isHAL (Just
( External ( External (HAL _ ) )
( Just (HAL _ )
)
)
) = true ) = true
isHAL _ = false isHAL _ = false
isIsTex :: Maybe DataField -> Boolean isIsTex :: Maybe DataField -> Boolean
isIsTex ( Just isIsTex ( Just
( External ( External ( IsTex ) )
( Just ( IsTex)
)
)
) = true ) = true
isIsTex _ = false isIsTex _ = false
...@@ -209,11 +201,8 @@ isIsTex _ = false ...@@ -209,11 +201,8 @@ isIsTex _ = false
isIMT :: Maybe DataField -> Boolean isIMT :: Maybe DataField -> Boolean
isIMT ( Just isIMT ( Just
( External ( External
( Just ( HAL
( HAL ( Just ( IMT _) )
( Just ( IMT _)
)
)
) )
) )
) = true ) = true
...@@ -222,24 +211,24 @@ isIMT _ = false ...@@ -222,24 +211,24 @@ isIMT _ = false
isCNRS :: Maybe DataField -> Boolean isCNRS :: Maybe DataField -> Boolean
isCNRS ( Just isCNRS ( Just
( External ( External
( Just ( HAL
( HAL ( Just ( CNRS _) )
( Just ( CNRS _) )
) )
)
)
)
) = true ) = true
isCNRS _ = false isCNRS _ = false
isPubmed :: Maybe DataField -> Boolean
isPubmed ( Just
( External ( PubMed _ ) )
) = true
isPubmed _ = false
needsLang :: Maybe DataField -> Boolean needsLang :: Maybe DataField -> Boolean
needsLang (Just Gargantext) = true needsLang (Just Gargantext) = true
needsLang (Just Web) = true needsLang (Just Web) = true
needsLang ( Just needsLang ( Just
( External ( External (HAL _) )
( Just (HAL _)
)
)
) = true ) = true
needsLang _ = false needsLang _ = false
...@@ -247,11 +236,9 @@ needsLang _ = false ...@@ -247,11 +236,9 @@ needsLang _ = false
isIn :: IMT_org -> Maybe DataField -> Boolean isIn :: IMT_org -> Maybe DataField -> Boolean
isIn org ( Just isIn org ( Just
( External ( External
( Just ( HAL
( HAL ( Just
( Just ( IMT imtOrgs )
( IMT imtOrgs )
)
) )
) )
) )
...@@ -259,8 +246,8 @@ isIn org ( Just ...@@ -259,8 +246,8 @@ isIn org ( Just
isIn _ _ = false isIn _ _ = false
updateFilter :: IMT_org -> Array IMT_org -> Maybe DataField -> Maybe DataField updateFilter :: IMT_org -> Array IMT_org -> Maybe DataField -> Maybe DataField
updateFilter org allIMTorgs (Just (External (Just (HAL (Just (IMT imtOrgs)))))) = updateFilter org allIMTorgs (Just (External (HAL (Just (IMT imtOrgs))))) =
(Just (External (Just (HAL (Just $ IMT imtOrgs'))))) Just $ External $ HAL $ Just $ IMT imtOrgs'
where where
imtOrgs' = if Set.member org imtOrgs imtOrgs' = if Set.member org imtOrgs
then then
...@@ -272,7 +259,7 @@ updateFilter org allIMTorgs (Just (External (Just (HAL (Just (IMT imtOrgs)))))) ...@@ -272,7 +259,7 @@ updateFilter org allIMTorgs (Just (External (Just (HAL (Just (IMT imtOrgs))))))
then Set.fromFoldable allIMTorgs then Set.fromFoldable allIMTorgs
else Set.insert org imtOrgs else Set.insert org imtOrgs
updateFilter org allIMTorgs _ = (Just (External (Just (HAL (Just (IMT imtOrgs')))))) updateFilter org allIMTorgs _ = (Just (External (HAL (Just (IMT imtOrgs')))))
where where
imtOrgs' = if org == All_IMT imtOrgs' = if org == All_IMT
then Set.fromFoldable allIMTorgs then Set.fromFoldable allIMTorgs
...@@ -346,6 +333,7 @@ dataFieldNavCpt = here.component "dataFieldNav" cpt ...@@ -346,6 +333,7 @@ dataFieldNavCpt = here.component "dataFieldNav" cpt
type DatabaseInputProps = ( type DatabaseInputProps = (
databases :: Array Database databases :: Array Database
, search :: T.Box Search , search :: T.Box Search
, session :: Session
) )
databaseInput :: R2.Component DatabaseInputProps databaseInput :: R2.Component DatabaseInputProps
...@@ -354,22 +342,36 @@ databaseInputCpt :: R.Component DatabaseInputProps ...@@ -354,22 +342,36 @@ databaseInputCpt :: R.Component DatabaseInputProps
databaseInputCpt = here.component "databaseInput" cpt databaseInputCpt = here.component "databaseInput" cpt
where where
cpt { databases cpt { databases
, search } _ = do , search
, session } _ = do
search' <- T.useLive T.unequal search search' <- T.useLive T.unequal search
let db = case search'.datafield of let db = case search'.datafield of
(Just (External (Just x))) -> Just x (Just (External x)) -> Just x
_ -> Nothing _ -> Nothing
liItem :: Database -> R.Element liItem :: Database -> R.Element
liItem db' = H.option { className : "text-primary center" liItem db' = H.option { className : "text-primary center"
, value: show db' } [ H.text (show db') ] , value: dbToInputValue db' } [ H.text (show db') ]
change e = do change e = do
let value = read $ R.unsafeEventValue e let value = dbFromInputValue $ R.unsafeEventValue e
T.modify_ (_ { datafield = Just $ External value -- TODO Fetch pubmed api key
, databases = fromMaybe Empty value launchAff_ $ do
}) search updatedValue <- case value of
Just (PubMed _) ->
case search'.node_id of
Just nodeId -> do
eCorpus <- getNodeCorpus session nodeId
case eCorpus of
Left _err -> pure $ PubMed { api_key: Nothing }
Right c -> pure $ PubMed { api_key: c.pubmedAPIKey }
Nothing -> pure $ PubMed { api_key: Nothing }
_ -> pure $ fromMaybe Empty value
liftEffect $ T.modify_ (_ { datafield = Just $ External updatedValue
, databases = updatedValue
}) search
pure $ pure $
H.div { className: "form-group" } H.div { className: "form-group" }
...@@ -384,6 +386,40 @@ databaseInputCpt = here.component "databaseInput" cpt ...@@ -384,6 +386,40 @@ databaseInputCpt = here.component "databaseInput" cpt
defaultValue datafield = show $ maybe Empty datafield2database datafield defaultValue datafield = show $ maybe Empty datafield2database datafield
type PubmedInputProps = (
search :: T.Box Search
, session :: Session
)
pubmedInput :: R2.Component PubmedInputProps
pubmedInput = R.createElement pubmedInputCpt
pubmedInputCpt :: R.Component PubmedInputProps
pubmedInputCpt = here.component "pubmedInput" cpt where
cpt { search, session } _ = do
search' <- T.useLive T.unequal search
case search'.datafield of
Just (External (PubMed p@{ api_key })) ->
-- TODO Fetch current API key
pure $
H.div { className: "form-group" }
[ H.div { className: "text-primary center" } [ H.text "Pubmed API key" ]
, H.input { className: "form-control"
, defaultValue: fromMaybe "" api_key
, on: { blur: modifyPubmedAPIKey search p
, change: modifyPubmedAPIKey search p
, input: modifyPubmedAPIKey search p } } ]
_ -> pure $ H.div {} []
where
modifyPubmedAPIKey search p e = do
let val = R.unsafeEventValue e
let mVal = case val of
"" -> Nothing
s -> Just s
T.modify_ (\s ->
s { datafield = Just (External (PubMed p { api_key = mVal })) }) search
type OrgInputProps = type OrgInputProps =
( orgs :: Array Org ( orgs :: Array Org
| ComponentProps) | ComponentProps)
...@@ -396,7 +432,7 @@ orgInputCpt = here.component "orgInput" cpt ...@@ -396,7 +432,7 @@ orgInputCpt = here.component "orgInput" cpt
cpt { orgs, search } _ = do cpt { orgs, search } _ = do
let change e = do let change e = do
let value = R.unsafeEventValue e let value = R.unsafeEventValue e
T.modify_ (_ { datafield = Just $ External $ Just $ HAL $ read value }) search T.modify_ (_ { datafield = Just $ External $ HAL $ read value }) search
pure $ H.div { className: "form-group" } pure $ H.div { className: "form-group" }
[ H.div {className: "text-primary center"} [H.text "filter with organization: "] [ H.div {className: "text-primary center"} [H.text "filter with organization: "]
...@@ -438,13 +474,18 @@ datafieldInputCpt :: R.Component DatafieldInputProps ...@@ -438,13 +474,18 @@ datafieldInputCpt :: R.Component DatafieldInputProps
datafieldInputCpt = here.component "datafieldInput" cpt where datafieldInputCpt = here.component "datafieldInput" cpt where
cpt { databases, langs, search, session } _ = do cpt { databases, langs, search, session } _ = do
search' <- T.useLive T.unequal search search' <- T.useLive T.unequal search
datafield <- T.useFocused (_.datafield) (\a b -> b { datafield = a }) search
iframeRef <- R.useRef null iframeRef <- R.useRef null
pure $ H.div {} pure $ H.div {}
[ dataFieldNav { search } [] [ dataFieldNav { search } []
, if isExternal search'.datafield , if isExternal search'.datafield
then databaseInput { databases, search } [] then databaseInput { databases, search, session } []
else H.div {} []
, if isPubmed search'.datafield
then pubmedInput { search, session } []
else H.div {} [] else H.div {} []
, if isHAL search'.datafield , if isHAL search'.datafield
...@@ -594,38 +635,41 @@ searchQuery selection { datafield: Nothing, term } = ...@@ -594,38 +635,41 @@ searchQuery selection { datafield: Nothing, term } =
, selection = selection }) defaultSearchQuery , selection = selection }) defaultSearchQuery
-- TODO Simplify both HAL Nothing and HAL (Just IMT) cases -- TODO Simplify both HAL Nothing and HAL (Just IMT) cases
searchQuery selection { databases searchQuery selection { databases
, datafield: datafield@(Just (External (Just (HAL Nothing)))) , datafield: datafield@(Just (External (HAL Nothing)))
, lang , lang
, term , term
, node_id , node_id
, years } = over SearchQuery (_ { databases = databases , years } =
, datafield = datafield over SearchQuery (_ { databases = databases
, lang = lang , datafield = datafield
, node_id = node_id , lang = lang
, query = queryHAL term Nothing lang years , node_id = node_id
, selection = selection , query = queryHAL term Nothing lang years
}) defaultSearchQuery , selection = selection
}) defaultSearchQuery
searchQuery selection { databases searchQuery selection { databases
, datafield: datafield@(Just (External (Just (HAL (Just (IMT imtOrgs)))))) , datafield: datafield@(Just (External (HAL (Just (IMT imtOrgs)))))
, lang , lang
, term , term
, node_id , node_id
, years } = over SearchQuery (_ { databases = databases , years } =
, datafield = datafield over SearchQuery (_ { databases = databases
, lang = lang , datafield = datafield
, node_id = node_id , lang = lang
, query = queryHAL term (Just imtOrgs) lang years , node_id = node_id
, selection = selection , query = queryHAL term (Just imtOrgs) lang years
}) defaultSearchQuery , selection = selection
}) defaultSearchQuery
searchQuery selection { databases, datafield, lang, term, node_id } = searchQuery selection { databases, datafield, lang, term, node_id } =
over SearchQuery (_ { databases = databases over SearchQuery (_ { databases = databases
, datafield = datafield , datafield = datafield
, lang = lang , lang = lang
, node_id = node_id , node_id = node_id
, query = term , query = term
, selection = selection , selection = selection
}) defaultSearchQuery }) defaultSearchQuery
queryHAL :: String -> Maybe (Set.Set IMT_org) -> Maybe Lang -> Array String -> String queryHAL :: String -> Maybe (Set.Set IMT_org) -> Maybe Lang -> Array String -> String
queryHAL term mIMTOrgs lang years = queryHAL term mIMTOrgs lang years =
......
...@@ -8,7 +8,6 @@ import Data.Maybe (Maybe(..), fromMaybe, maybe) ...@@ -8,7 +8,6 @@ import Data.Maybe (Maybe(..), fromMaybe, maybe)
import Data.Newtype (class Newtype) import Data.Newtype (class Newtype)
import Data.Set (Set) import Data.Set (Set)
import Data.Set as Set import Data.Set as Set
import Data.String as String
import Data.Tuple (Tuple) import Data.Tuple (Tuple)
import Data.Tuple.Nested ((/\)) import Data.Tuple.Nested ((/\))
import Gargantext.Components.GraphQL.IMT as GQLIMT import Gargantext.Components.GraphQL.IMT as GQLIMT
...@@ -23,21 +22,18 @@ import Simple.JSON as JSON ...@@ -23,21 +22,18 @@ import Simple.JSON as JSON
import URI.Extra.QueryPairs as QP import URI.Extra.QueryPairs as QP
import URI.Query as Q import URI.Query as Q
type Search = { databases :: Database type Search = { databases :: Database
, datafield :: Maybe DataField , datafield :: Maybe DataField
, url :: String , url :: String
, lang :: Maybe Lang , lang :: Maybe Lang
, node_id :: Maybe Int , node_id :: Maybe Int
, term :: String , term :: String
, years :: Array String , years :: Array String
} }
isIsTex_Advanced :: Maybe DataField -> Boolean isIsTex_Advanced :: Maybe DataField -> Boolean
isIsTex_Advanced ( Just isIsTex_Advanced ( Just
( External ( External ( IsTex_Advanced) )
( Just ( IsTex_Advanced)
)
)
) = true ) = true
isIsTex_Advanced _ = false isIsTex_Advanced _ = false
...@@ -51,13 +47,13 @@ class Doc a where ...@@ -51,13 +47,13 @@ class Doc a where
dataFields :: Array DataField dataFields :: Array DataField
dataFields = [ {- Gargantext dataFields = [ {- Gargantext
, -} External Nothing , -} External Empty
, Web , Web
-- , Files -- , Files
] ]
data DataField = Gargantext data DataField = Gargantext
| External (Maybe Database) | External Database
| Web | Web
| Files | Files
...@@ -74,9 +70,9 @@ instance Doc DataField where ...@@ -74,9 +70,9 @@ instance Doc DataField where
doc Files = "Zip files with formats.." doc Files = "Zip files with formats.."
derive instance Eq DataField derive instance Eq DataField
instance JSON.WriteForeign DataField where instance JSON.WriteForeign DataField where
writeImpl (External (Just db)) = JSON.writeImpl $ "External " <> show db writeImpl (External db) = JSON.writeImpl { tag: "External"
writeImpl Web = JSON.writeImpl $ "Web" , contents: JSON.writeImpl db }
writeImpl f = JSON.writeImpl $ show f writeImpl f = JSON.writeImpl $ JSON.writeImpl { tag: show f }
---------------------------------------- ----------------------------------------
data DataOriginApi = InternalOrigin { api :: Database } data DataOriginApi = InternalOrigin { api :: Database }
...@@ -91,19 +87,19 @@ instance JSON.WriteForeign DataOriginApi where ...@@ -91,19 +87,19 @@ instance JSON.WriteForeign DataOriginApi where
writeImpl (ExternalOrigin { api }) = JSON.writeImpl { api } writeImpl (ExternalOrigin { api }) = JSON.writeImpl { api }
datafield2dataOriginApi :: DataField -> DataOriginApi datafield2dataOriginApi :: DataField -> DataOriginApi
datafield2dataOriginApi (External (Just a)) = ExternalOrigin { api : a } datafield2dataOriginApi (External a) = ExternalOrigin { api : a }
datafield2dataOriginApi _ = InternalOrigin { api : IsTex } -- TODO fixme datafield2dataOriginApi _ = InternalOrigin { api : IsTex } -- TODO fixme
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- | Database search specifications -- | Database search specifications
datafield2database :: DataField -> Database datafield2database :: DataField -> Database
datafield2database (External (Just x)) = x datafield2database (External x) = x
datafield2database _ = Empty datafield2database _ = Empty
allDatabases :: Array Database allDatabases :: Array Database
allDatabases = [ Empty allDatabases = [ Empty
, PubMed , PubMed { api_key: Nothing }
, Arxiv , Arxiv
, HAL Nothing , HAL Nothing
, IsTex , IsTex
...@@ -116,7 +112,7 @@ allDatabases = [ Empty ...@@ -116,7 +112,7 @@ allDatabases = [ Empty
data Database = All_Databases data Database = All_Databases
| Empty | Empty
| PubMed | PubMed { api_key :: Maybe String }
| Arxiv | Arxiv
| HAL (Maybe Org) | HAL (Maybe Org)
| IsTex | IsTex
...@@ -127,7 +123,7 @@ data Database = All_Databases ...@@ -127,7 +123,7 @@ data Database = All_Databases
derive instance Generic Database _ derive instance Generic Database _
instance Show Database where instance Show Database where
show All_Databases = "All Databases" show All_Databases = "All Databases"
show PubMed = "PubMed" show (PubMed _) = "PubMed"
show Arxiv = "Arxiv" show Arxiv = "Arxiv"
show (HAL _) = "HAL" show (HAL _) = "HAL"
show IsTex = "IsTex" show IsTex = "IsTex"
...@@ -139,7 +135,7 @@ instance Show Database where ...@@ -139,7 +135,7 @@ instance Show Database where
instance Doc Database where instance Doc Database where
doc All_Databases = "All databases" doc All_Databases = "All databases"
doc PubMed = "All Medical publications" doc (PubMed _) = "All Medical publications"
doc Arxiv = "Arxiv" doc Arxiv = "Arxiv"
doc (HAL _) = "All open science (archives ouvertes)" doc (HAL _) = "All open science (archives ouvertes)"
doc IsTex = "All Elsevier enriched by CNRS/INIST" doc IsTex = "All Elsevier enriched by CNRS/INIST"
...@@ -149,22 +145,46 @@ instance Doc Database where ...@@ -149,22 +145,46 @@ instance Doc Database where
-- doc News = "Web filtered by News" -- doc News = "Web filtered by News"
-- doc SocialNetworks = "Web filtered by MicroBlogs" -- doc SocialNetworks = "Web filtered by MicroBlogs"
instance Read Database where -- instance Read Database where
read :: String -> Maybe Database -- read :: String -> Maybe Database
read "All Databases" = Just All_Databases -- read "All Databases" = Just All_Databases
read "PubMed" = Just PubMed -- read "PubMed" = Just PubMed
read "Arxiv" = Just Arxiv -- read "Arxiv" = Just Arxiv
read "HAL" = Just $ HAL Nothing -- read "HAL" = Just $ HAL Nothing
read "Isidore" = Just Isidore -- read "Isidore" = Just Isidore
read "IsTex" = Just IsTex -- read "IsTex" = Just IsTex
read "IsTex_Advanced" = Just IsTex_Advanced -- read "IsTex_Advanced" = Just IsTex_Advanced
-- read "Web" = Just Web -- -- read "Web" = Just Web
-- read "News" = Just News -- -- read "News" = Just News
-- read "Social Networks" = Just SocialNetworks -- -- read "Social Networks" = Just SocialNetworks
read _ = Nothing -- read _ = Nothing
dbToInputValue :: Database -> String
dbToInputValue All_Databases = "all_databases"
dbToInputValue (PubMed _) = "pubmed"
dbToInputValue Arxiv = "arxiv"
dbToInputValue (HAL _) = "hal"
dbToInputValue IsTex = "istex"
dbToInputValue IsTex_Advanced = "istex_advanced"
dbToInputValue Isidore = "isidore"
dbToInputValue Empty = "empty"
dbFromInputValue :: String -> Maybe Database
dbFromInputValue "all_databases" = Just All_Databases
dbFromInputValue "pubmed" = Just (PubMed { api_key: Nothing})
dbFromInputValue "arxiv" = Just Arxiv
dbFromInputValue "hal" = Just (HAL Nothing)
dbFromInputValue "istex" = Just IsTex
dbFromInputValue "istex_advanced" = Just IsTex_Advanced
dbFromInputValue "isidore" = Just Isidore
dbFromInputValue "empty" = Just Empty
dbFromInputValue _ = Nothing
derive instance Eq Database derive instance Eq Database
instance JSON.WriteForeign Database where writeImpl = JSON.writeImpl <<< show instance JSON.WriteForeign Database where
writeImpl (PubMed { api_key }) = JSON.writeImpl { tag: "PubMed"
, _api_key: api_key }
writeImpl f = JSON.writeImpl { tag: show f }
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- | Organization specifications -- | Organization specifications
...@@ -234,16 +254,17 @@ instance Show SearchOrder where ...@@ -234,16 +254,17 @@ instance Show SearchOrder where
------------------------------------------------------------------------ ------------------------------------------------------------------------
newtype SearchQuery = SearchQuery newtype SearchQuery = SearchQuery
{ query :: String { query :: String
, databases :: Database , databases :: Database
, datafield :: Maybe DataField , datafield :: Maybe DataField
, files_id :: Array String , files_id :: Array String
, lang :: Maybe Lang , lang :: Maybe Lang
, limit :: Maybe Int , limit :: Maybe Int
, node_id :: Maybe Int , node_id :: Maybe Int
, offset :: Maybe Int , offset :: Maybe Int
, order :: Maybe SearchOrder , order :: Maybe SearchOrder
, selection :: ListSelection.Selection , pubmedAPIKey :: Maybe String
, selection :: ListSelection.Selection
} }
derive instance Generic SearchQuery _ derive instance Generic SearchQuery _
derive instance Newtype SearchQuery _ derive instance Newtype SearchQuery _
...@@ -260,27 +281,29 @@ instance GT.ToQuery SearchQuery where ...@@ -260,27 +281,29 @@ instance GT.ToQuery SearchQuery where
pair k = maybe [] $ \v -> pair k = maybe [] $ \v ->
[ QP.keyFromString k /\ Just (QP.valueFromString $ show v) ] [ QP.keyFromString k /\ Just (QP.valueFromString $ show v) ]
instance JSON.WriteForeign SearchQuery where instance JSON.WriteForeign SearchQuery where
writeImpl (SearchQuery { databases, datafield, lang, node_id, query, selection }) = writeImpl (SearchQuery { databases, datafield, lang, node_id, pubmedAPIKey, query, selection }) =
JSON.writeImpl { query: query -- String.replace (String.Pattern "\"") (String.Replacement "\\\"") query JSON.writeImpl { query: query -- String.replace (String.Pattern "\"") (String.Replacement "\\\"") query
, databases , databases
, datafield , datafield
, lang: maybe "EN" show lang , lang: maybe "EN" show lang
, node_id: fromMaybe 0 node_id , node_id: fromMaybe 0 node_id
, flowListWith: selection , flowListWith: selection
, pubmedAPIKey
} }
defaultSearchQuery :: SearchQuery defaultSearchQuery :: SearchQuery
defaultSearchQuery = SearchQuery defaultSearchQuery = SearchQuery
{ query : "" { query : ""
, databases : Empty , databases : Empty
, datafield : Nothing , datafield : Nothing
, files_id : [] , files_id : []
, lang : Nothing , lang : Nothing
, limit : Nothing , limit : Nothing
, node_id : Nothing , node_id : Nothing
, offset : Nothing , offset : Nothing
, order : Nothing , order : Nothing
, selection : ListSelection.NoList -- MyListsFirst , pubmedAPIKey : Nothing
, selection : ListSelection.NoList -- MyListsFirst
} }
performSearch :: Session -> Int -> SearchQuery -> AffRESTError GT.AsyncTaskWithType performSearch :: Session -> Int -> SearchQuery -> AffRESTError GT.AsyncTaskWithType
......
...@@ -14,7 +14,7 @@ import Gargantext.Components.GraphQL.Contact (AnnuaireContact) ...@@ -14,7 +14,7 @@ import Gargantext.Components.GraphQL.Contact (AnnuaireContact)
import Gargantext.Components.GraphQL.Context as GQLCTX import Gargantext.Components.GraphQL.Context as GQLCTX
import Gargantext.Components.GraphQL.IMT as GQLIMT import Gargantext.Components.GraphQL.IMT as GQLIMT
import Gargantext.Components.GraphQL.NLP as GQLNLP import Gargantext.Components.GraphQL.NLP as GQLNLP
import Gargantext.Components.GraphQL.Node (Node) import Gargantext.Components.GraphQL.Node as GQLNode
import Gargantext.Components.GraphQL.Tree (TreeFirstLevel) import Gargantext.Components.GraphQL.Tree (TreeFirstLevel)
import Gargantext.Components.GraphQL.User (User, UserInfo, UserInfoM) import Gargantext.Components.GraphQL.User (User, UserInfo, UserInfoM)
import Gargantext.Components.GraphQL.Team (Team, TeamDeleteM) import Gargantext.Components.GraphQL.Team (Team, TeamDeleteM)
...@@ -78,8 +78,9 @@ type Schema ...@@ -78,8 +78,9 @@ type Schema
, contexts_for_ngrams :: { corpus_id :: Int, ngrams_terms :: Array String } ==> Array GQLCTX.Context , contexts_for_ngrams :: { corpus_id :: Int, ngrams_terms :: Array String } ==> Array GQLCTX.Context
, imt_schools :: {} ==> Array GQLIMT.School , imt_schools :: {} ==> Array GQLIMT.School
, languages :: {} ==> Array GQLNLP.Language , languages :: {} ==> Array GQLNLP.Language
, node_parent :: { node_id :: Int, parent_type :: String } ==> Array Node -- TODO: parent_type :: NodeType , node_parent :: { node_id :: Int, parent_type :: String } ==> Array GQLNode.Node -- TODO: parent_type :: NodeType
, nodes :: { node_id :: Int } ==> Array Node , nodes :: { node_id :: Int } ==> Array GQLNode.Node
, nodes_corpus :: { corpus_id :: Int } ==> Array GQLNode.Corpus
, user_infos :: { user_id :: Int } ==> Array UserInfo , user_infos :: { user_id :: Int } ==> Array UserInfo
, users :: { user_id :: Int } ==> Array User , users :: { user_id :: Int } ==> Array User
, team :: { team_node_id :: Int } ==> Team , team :: { team_node_id :: Int } ==> Team
......
...@@ -14,7 +14,7 @@ import Gargantext.Components.GraphQL.Contact (AnnuaireContact, annuaireContactQu ...@@ -14,7 +14,7 @@ import Gargantext.Components.GraphQL.Contact (AnnuaireContact, annuaireContactQu
import Gargantext.Components.GraphQL.Context as GQLCTX import Gargantext.Components.GraphQL.Context as GQLCTX
import Gargantext.Components.GraphQL.IMT as GQLIMT import Gargantext.Components.GraphQL.IMT as GQLIMT
import Gargantext.Components.GraphQL.NLP as GQLNLP import Gargantext.Components.GraphQL.NLP as GQLNLP
import Gargantext.Components.GraphQL.Node (Node, nodeParentQuery, nodesQuery) import Gargantext.Components.GraphQL.Node (Corpus, Node, nodeParentQuery, nodesQuery, nodesCorpusQuery)
import Gargantext.Components.GraphQL.Team (Team, teamQuery) import Gargantext.Components.GraphQL.Team (Team, teamQuery)
import Gargantext.Components.GraphQL.Tree (TreeFirstLevel, treeFirstLevelQuery) import Gargantext.Components.GraphQL.Tree (TreeFirstLevel, treeFirstLevelQuery)
import Gargantext.Components.GraphQL.User (UserInfo, userInfoQuery) import Gargantext.Components.GraphQL.User (UserInfo, userInfoQuery)
...@@ -46,6 +46,15 @@ getNode session nodeId = do ...@@ -46,6 +46,15 @@ getNode session nodeId = do
Nothing -> Left (CustomError $ "node with id" <> show nodeId <>" not found") Nothing -> Left (CustomError $ "node with id" <> show nodeId <>" not found")
Just node -> Right node Just node -> Right node
getNodeCorpus :: Session -> Int -> AffRESTError Corpus
getNodeCorpus session corpusId = do
{ nodes_corpus } <- queryGql session "get nodes corpus" $
nodesCorpusQuery `withVars` { id: corpusId }
liftEffect $ here.log2 "[getNodesCorpus] nodes_corpus" nodes_corpus
pure $ case A.head nodes_corpus of
Nothing -> Left (CustomError $ "corpus with id" <> show corpusId <>" not found")
Just corpus -> Right corpus
getNodeParent :: Session -> Int -> NodeType -> Aff (Array Node) getNodeParent :: Session -> Int -> NodeType -> Aff (Array Node)
getNodeParent session nodeId parentType = do getNodeParent session nodeId parentType = do
{ node_parent } <- queryGql session "get node parent" $ { node_parent } <- queryGql session "get node parent" $
......
...@@ -2,18 +2,35 @@ module Gargantext.Components.GraphQL.Node where ...@@ -2,18 +2,35 @@ module Gargantext.Components.GraphQL.Node where
import Gargantext.Prelude import Gargantext.Prelude
import Data.Maybe (Maybe)
import GraphQL.Client.Args (Args, (=>>)) import GraphQL.Client.Args (Args, (=>>))
import GraphQL.Client.Variable (Var(..)) import GraphQL.Client.Variable (Var(..))
import Gargantext.Utils.GraphQL as GGQL import Gargantext.Utils.GraphQL as GGQL
import Type.Proxy (Proxy(..)) import Type.Proxy (Proxy(..))
type Corpus
= { id :: Int
, name :: String
, parent_id :: Int
, pubmedAPIKey :: Maybe String
, type_id :: Int }
type Node type Node
= { id :: Int = { id :: Int
, name :: String , name :: String
, parent_id :: Int , parent_id :: Int
, type_id :: Int } , type_id :: Int }
type NodesCorpusQuery =
{ nodes_corpus :: Args
{ corpus_id :: Var "id" Int }
{ id :: Unit
, name :: Unit
, parent_id :: Unit
, pubmedAPIKey :: Unit
, type_id :: Unit } }
type NodesQuery = type NodesQuery =
{ nodes :: Args { nodes :: Args
{ node_id :: Var "id" Int } { node_id :: Var "id" Int }
...@@ -27,6 +44,11 @@ nodesQuery = { nodes: { node_id: Var :: _ "id" Int } =>> ...@@ -27,6 +44,11 @@ nodesQuery = { nodes: { node_id: Var :: _ "id" Int } =>>
GGQL.getFieldsStandard (Proxy :: _ Node) GGQL.getFieldsStandard (Proxy :: _ Node)
} }
nodesCorpusQuery :: NodesCorpusQuery
nodesCorpusQuery = { nodes_corpus: { corpus_id: Var :: _ "id" Int } =>>
GGQL.getFieldsStandard (Proxy :: _ Corpus)
}
nodeParentQuery = { node_parent: { node_id: Var :: _ "id" Int nodeParentQuery = { node_parent: { node_id: Var :: _ "id" Int
, parent_type: Var :: _ "parent_type" String } =>> -- TODO parent_type :: NodeType , parent_type: Var :: _ "parent_type" String } =>> -- TODO parent_type :: NodeType
GGQL.getFieldsStandard (Proxy :: _ Node) GGQL.getFieldsStandard (Proxy :: _ Node)
......
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