[ngrams] simplify WithQuery json structure

There is now only a 'datafield' field, no need for duplicated
'database'.

Related to #441
parent e6fdbee4
Pipeline #7203 failed with stages
in 52 minutes and 47 seconds
...@@ -788,6 +788,7 @@ test-suite garg-test-tasty ...@@ -788,6 +788,7 @@ test-suite garg-test-tasty
Test.API.Prelude Test.API.Prelude
Test.API.UpdateList Test.API.UpdateList
Test.Core.Notifications Test.Core.Notifications
Test.Core.Orchestrator
Test.Core.Similarity Test.Core.Similarity
Test.Core.Text Test.Core.Text
Test.Core.Text.Corpus.Query Test.Core.Text.Corpus.Query
......
...@@ -17,7 +17,8 @@ Portability : POSIX ...@@ -17,7 +17,8 @@ Portability : POSIX
module Gargantext.API.Admin.Orchestrator.Types module Gargantext.API.Admin.Orchestrator.Types
where where
import Data.Aeson (genericParseJSON, genericToJSON) import Data.Aeson (genericParseJSON, genericToJSON, object, withObject, (.=), (.:), (.:?), Value(String))
import Data.Aeson.Types (unexpected)
import Data.Morpheus.Types ( GQLType(..), DropNamespace(..), typeDirective ) import Data.Morpheus.Types ( GQLType(..), DropNamespace(..), typeDirective )
import Data.Swagger (ToSchema, URL, declareNamedSchema, defaultSchemaOptions, genericDeclareNamedSchemaUnrestricted) import Data.Swagger (ToSchema, URL, declareNamedSchema, defaultSchemaOptions, genericDeclareNamedSchemaUnrestricted)
-- import Gargantext.API.GraphQL.UnPrefix qualified as GQLU -- import Gargantext.API.GraphQL.UnPrefix qualified as GQLU
...@@ -42,8 +43,24 @@ data ExternalAPIs = OpenAlex ...@@ -42,8 +43,24 @@ data ExternalAPIs = OpenAlex
-- | Main Instances -- | Main Instances
instance FromJSON ExternalAPIs instance FromJSON ExternalAPIs where
instance ToJSON ExternalAPIs parseJSON = withObject "ExternalAPIs" $ \o -> do
db <- o .: "db"
case db of
"OpenAlex" -> pure OpenAlex
"PubMed" -> do
mAPIKey <- o .:? "api_key"
pure $ PubMed mAPIKey
"Arxiv" -> pure Arxiv
"HAL" -> pure HAL
"IsTex" -> pure IsTex
"Isidore" -> pure Isidore
"EPO" -> pure EPO
s -> unexpected (String s)
instance ToJSON ExternalAPIs where
toJSON (PubMed mAPIKey) = object [ "db" .= toJSON ("PubMed" :: Text)
, "api_key" .= toJSON mAPIKey ]
toJSON t = object [ "db" .= toJSON (show t :: Text) ]
externalAPIs :: [ExternalAPIs] externalAPIs :: [ExternalAPIs]
externalAPIs = externalAPIs =
...@@ -55,10 +72,6 @@ externalAPIs = ...@@ -55,10 +72,6 @@ externalAPIs =
, Isidore , Isidore
, EPO ] , EPO ]
instance Arbitrary ExternalAPIs
where
arbitrary = elements externalAPIs
instance ToSchema ExternalAPIs where instance ToSchema ExternalAPIs where
declareNamedSchema = genericDeclareNamedSchemaUnrestricted defaultSchemaOptions declareNamedSchema = genericDeclareNamedSchemaUnrestricted defaultSchemaOptions
......
...@@ -32,7 +32,7 @@ import Gargantext.API.Admin.Orchestrator.Types qualified as API ...@@ -32,7 +32,7 @@ import Gargantext.API.Admin.Orchestrator.Types qualified as API
import Gargantext.API.Ngrams (commitStatePatch, Versioned(..)) import Gargantext.API.Ngrams (commitStatePatch, Versioned(..))
import Gargantext.API.Node.Corpus.New.Types ( FileFormat(..), FileType(..) ) import Gargantext.API.Node.Corpus.New.Types ( FileFormat(..), FileType(..) )
import Gargantext.API.Node.Corpus.Searx ( triggerSearxSearch ) import Gargantext.API.Node.Corpus.Searx ( triggerSearxSearch )
import Gargantext.API.Node.Corpus.Types ( Datafield(Web), database2origin ) import Gargantext.API.Node.Corpus.Types ( Datafield(Web), datafield2origin )
import Gargantext.API.Node.Corpus.Update (addLanguageToCorpus) import Gargantext.API.Node.Corpus.Update (addLanguageToCorpus)
import Gargantext.API.Node.Types import Gargantext.API.Node.Types
import Gargantext.Core (withDefaultLanguage, defaultLanguage) import Gargantext.Core (withDefaultLanguage, defaultLanguage)
...@@ -155,13 +155,12 @@ addToCorpusWithQuery :: ( FlowCmdM env err m ...@@ -155,13 +155,12 @@ addToCorpusWithQuery :: ( FlowCmdM env err m
-> JobHandle m -> JobHandle m
-> m () -> m ()
addToCorpusWithQuery user cid (WithQuery { _wq_query = q addToCorpusWithQuery user cid (WithQuery { _wq_query = q
, _wq_databases = dbs
, _wq_datafield = datafield , _wq_datafield = datafield
, _wq_lang = l , _wq_lang = l
, _wq_flowListWith = flw , _wq_flowListWith = flw
, .. }) maybeLimit jobHandle = do , .. }) maybeLimit jobHandle = do
-- TODO ... -- TODO ...
$(logLocM) DEBUG $ "[addToCorpusWithQuery] (cid, dbs) " <> show (cid, dbs) $(logLocM) DEBUG $ "[addToCorpusWithQuery] cid " <> show cid
$(logLocM) DEBUG $ "[addToCorpusWithQuery] datafield " <> show datafield $(logLocM) DEBUG $ "[addToCorpusWithQuery] datafield " <> show datafield
$(logLocM) DEBUG $ "[addToCorpusWithQuery] flowListWith " <> show flw $(logLocM) DEBUG $ "[addToCorpusWithQuery] flowListWith " <> show flw
...@@ -173,7 +172,7 @@ addToCorpusWithQuery user cid (WithQuery { _wq_query = q ...@@ -173,7 +172,7 @@ addToCorpusWithQuery user cid (WithQuery { _wq_query = q
$(logLocM) DEBUG "[addToCorpusWithQuery] after addLanguageToCorpus" $(logLocM) DEBUG "[addToCorpusWithQuery] after addLanguageToCorpus"
case datafield of case datafield of
Just Web -> do Web -> do
$(logLocM) DEBUG $ "[addToCorpusWithQuery] processing web request " <> show datafield $(logLocM) DEBUG $ "[addToCorpusWithQuery] processing web request " <> show datafield
markStarted 1 jobHandle markStarted 1 jobHandle
...@@ -190,7 +189,7 @@ addToCorpusWithQuery user cid (WithQuery { _wq_query = q ...@@ -190,7 +189,7 @@ addToCorpusWithQuery user cid (WithQuery { _wq_query = q
-- if cid is corpus -> add to corpus -- if cid is corpus -> add to corpus
-- if cid is root -> create corpus in Private -- if cid is root -> create corpus in Private
$(logLocM) DEBUG $ "[addToCorpusWithQuery] getDataText with query: " <> show q $(logLocM) DEBUG $ "[addToCorpusWithQuery] getDataText with query: " <> show q
let db = database2origin dbs let db = datafield2origin datafield
-- mPubmedAPIKey <- getUserPubmedAPIKey user -- mPubmedAPIKey <- getUserPubmedAPIKey user
-- printDebug "[addToCorpusWithQuery] mPubmedAPIKey" mPubmedAPIKey -- printDebug "[addToCorpusWithQuery] mPubmedAPIKey" mPubmedAPIKey
eTxt <- getDataText db (Multi l) q mEPOAuthKey maybeLimit eTxt <- getDataText db (Multi l) q mEPOAuthKey maybeLimit
......
...@@ -9,17 +9,15 @@ Portability : POSIX ...@@ -9,17 +9,15 @@ Portability : POSIX
-} -}
{-# LANGUAGE TemplateHaskell #-}
module Gargantext.API.Node.Corpus.Types where module Gargantext.API.Node.Corpus.Types where
import Control.Lens ( (?~) ) import Control.Lens ( (?~) )
import Control.Monad.Fail (fail) import Control.Monad.Fail (fail)
import Data.Aeson ( Value(..), (.:), withText, object ) import Data.Aeson ( Value(..), (.:), (.:?), (.=), withText, object, withObject )
import Data.Aeson.Types (unexpected)
import Data.Swagger import Data.Swagger
import Data.Text qualified as T import Data.Text qualified as T
import Gargantext.API.Admin.Orchestrator.Types qualified as Types import Gargantext.API.Admin.Orchestrator.Types qualified as Types
import Gargantext.Core.Utils.Prefix (unPrefix)
import Gargantext.Database.Action.Flow.Types (DataOrigin(..)) import Gargantext.Database.Action.Flow.Types (DataOrigin(..))
import Gargantext.Prelude import Gargantext.Prelude
import PUBMED.Types qualified as PUBMED import PUBMED.Types qualified as PUBMED
...@@ -34,19 +32,39 @@ data Database = Empty ...@@ -34,19 +32,39 @@ data Database = Empty
| EPO | EPO
deriving (Eq, Show, Generic) deriving (Eq, Show, Generic)
deriveJSON (unPrefix "") ''Database instance FromJSON Database where
parseJSON = withObject "Database" $ \o -> do
db <- o .: "db"
case db of
"Empty" -> pure Empty
"OpenAlex" -> pure OpenAlex
"PubMed" -> do
mAPIKey <- o .:? "api_key"
pure $ PubMed mAPIKey
"Arxiv" -> pure Arxiv
"HAL" -> pure HAL
"IsTex" -> pure IsTex
"Isidore" -> pure Isidore
"EPO" -> pure EPO
s -> unexpected (String s)
instance ToJSON Database where
toJSON (PubMed mAPIKey) = object [ "db" .= toJSON ("PubMed" :: Text)
, "api_key" .= toJSON mAPIKey ]
toJSON t = object [ "db" .= toJSON (show t :: Text) ]
instance ToSchema Database where instance ToSchema Database where
declareNamedSchema = genericDeclareNamedSchemaUnrestricted defaultSchemaOptions declareNamedSchema = genericDeclareNamedSchemaUnrestricted defaultSchemaOptions
database2origin :: Database -> DataOrigin datafield2origin :: Datafield -> DataOrigin
database2origin Empty = InternalOrigin Types.IsTex datafield2origin (External Empty) = InternalOrigin Types.IsTex
database2origin OpenAlex = ExternalOrigin Types.OpenAlex datafield2origin (External OpenAlex) = ExternalOrigin Types.OpenAlex
database2origin (PubMed k) = ExternalOrigin (Types.PubMed k) datafield2origin (External (PubMed mAPIKey)) = ExternalOrigin (Types.PubMed mAPIKey)
database2origin Arxiv = ExternalOrigin Types.Arxiv datafield2origin (External Arxiv) = ExternalOrigin Types.Arxiv
database2origin HAL = ExternalOrigin Types.HAL datafield2origin (External HAL) = ExternalOrigin Types.HAL
database2origin IsTex = ExternalOrigin Types.IsTex datafield2origin (External IsTex) = ExternalOrigin Types.IsTex
database2origin Isidore = ExternalOrigin Types.Isidore datafield2origin (External Isidore) = ExternalOrigin Types.Isidore
database2origin EPO = ExternalOrigin Types.EPO datafield2origin (External EPO) = ExternalOrigin Types.EPO
-- | This isn't really used
datafield2origin _ = InternalOrigin Types.IsTex
------------------------------------------------------------------------ ------------------------------------------------------------------------
data Datafield = Gargantext data Datafield = Gargantext
......
...@@ -83,8 +83,7 @@ instance GargDB.SaveFile NewWithFile where ...@@ -83,8 +83,7 @@ instance GargDB.SaveFile NewWithFile where
data WithQuery = WithQuery data WithQuery = WithQuery
{ _wq_query :: !API.RawQuery { _wq_query :: !API.RawQuery
, _wq_databases :: !Database , _wq_datafield :: !Datafield
, _wq_datafield :: !(Maybe Datafield)
, _wq_lang :: !Lang , _wq_lang :: !Lang
, _wq_node_id :: !Int , _wq_node_id :: !Int
, _wq_flowListWith :: !FlowSocialListWith , _wq_flowListWith :: !FlowSocialListWith
......
...@@ -22,8 +22,6 @@ data_filepath = "~/.garg" ...@@ -22,8 +22,6 @@ data_filepath = "~/.garg"
#repo_filepath = "~/.garg" #repo_filepath = "~/.garg"
[apis] [apis]
[apis.pubmed]
api_key = "no_key"
[apis.epo] [apis.epo]
api_url = "" api_url = ""
......
{-|
Module : Core.Orchestrator
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
module Test.Core.Orchestrator
( qcTests )
where
import Data.Aeson qualified as A
import Gargantext.API.Admin.Orchestrator.Types
import Gargantext.Prelude
import Test.Instances ()
import Test.Tasty
import Test.Tasty.QuickCheck qualified as QC
qcTests :: TestTree
qcTests =
testGroup "Orchestrator QuickCheck tests" $ do
[ QC.testProperty "ExternalAPIs aeson encoding" $ \m -> A.decode (A.encode (m :: ExternalAPIs)) == Just m ]
...@@ -23,13 +23,15 @@ import Data.Text qualified as T ...@@ -23,13 +23,15 @@ import Data.Text qualified as T
import Data.Validity (Validation(..), ValidationChain (..), prettyValidation) import Data.Validity (Validation(..), ValidationChain (..), prettyValidation)
import EPO.API.Client.Types qualified as EPO import EPO.API.Client.Types qualified as EPO
import Gargantext.API.Admin.Auth.Types (AuthenticatedUser, ForgotPasswordAsyncParams) import Gargantext.API.Admin.Auth.Types (AuthenticatedUser, ForgotPasswordAsyncParams)
import Gargantext.API.Admin.Orchestrator.Types qualified as Orch
import Gargantext.API.Errors.Types qualified as Errors import Gargantext.API.Errors.Types qualified as Errors
import Gargantext.API.Ngrams.Types qualified as Ngrams import Gargantext.API.Ngrams.Types qualified as Ngrams
import Gargantext.API.Node.Contact.Types (AddContactParams) import Gargantext.API.Node.Contact.Types (AddContactParams)
import Gargantext.API.Node.Corpus.Annuaire (AnnuaireWithForm) import Gargantext.API.Node.Corpus.Annuaire (AnnuaireWithForm)
import Gargantext.API.Node.Corpus.New (ApiInfo) import Gargantext.API.Node.Corpus.New (ApiInfo)
import Gargantext.API.Node.Corpus.New.Types (FileFormat, FileType) import Gargantext.API.Node.Corpus.New.Types (FileFormat, FileType)
import Gargantext.API.Node.Corpus.Types (Datafield, Database) import Gargantext.API.Node.Corpus.Types (Datafield)
import Gargantext.API.Node.Corpus.Types qualified as CT
import Gargantext.API.Node.DocumentsFromWriteNodes.Types qualified as DFWN import Gargantext.API.Node.DocumentsFromWriteNodes.Types qualified as DFWN
import Gargantext.API.Node.DocumentUpload.Types (DocumentUpload) import Gargantext.API.Node.DocumentUpload.Types (DocumentUpload)
import Gargantext.API.Node.FrameCalcUpload.Types qualified as FCU import Gargantext.API.Node.FrameCalcUpload.Types qualified as FCU
...@@ -127,7 +129,15 @@ instance Arbitrary ApiInfo where arbitrary = genericArbitrary ...@@ -127,7 +129,15 @@ instance Arbitrary ApiInfo where arbitrary = genericArbitrary
instance Arbitrary FileFormat where arbitrary = genericArbitrary instance Arbitrary FileFormat where arbitrary = genericArbitrary
instance Arbitrary FileType where arbitrary = genericArbitrary instance Arbitrary FileType where arbitrary = genericArbitrary
instance Arbitrary Database where arbitrary = arbitraryBoundedEnum instance Arbitrary CT.Database where
arbitrary = oneof [ pure CT.Empty
, pure CT.OpenAlex
, CT.PubMed <$> arbitrary
, pure CT.Arxiv
, pure CT.HAL
, pure CT.IsTex
, pure CT.Isidore
, pure CT.EPO ]
instance Arbitrary Datafield where arbitrary = genericArbitrary instance Arbitrary Datafield where arbitrary = genericArbitrary
instance Arbitrary WithQuery where arbitrary = genericArbitrary instance Arbitrary WithQuery where arbitrary = genericArbitrary
...@@ -291,6 +301,17 @@ instance Arbitrary Hyperdata.HyperdataPublic where ...@@ -291,6 +301,17 @@ instance Arbitrary Hyperdata.HyperdataPublic where
arbitrary = pure Hyperdata.defaultHyperdataPublic arbitrary = pure Hyperdata.defaultHyperdataPublic
instance Arbitrary Orch.ExternalAPIs where
arbitrary = oneof [ pure Orch.OpenAlex
, Orch.PubMed <$> arbitrary
, pure Orch.Arxiv
, pure Orch.HAL
, pure Orch.IsTex
, pure Orch.Isidore
, pure Orch.EPO ]
-- instance Arbitrary NewWithFile where -- instance Arbitrary NewWithFile where
-- arbitrary = NewWithFile <$> arbitrary -- _wfi_b64_data -- arbitrary = NewWithFile <$> arbitrary -- _wfi_b64_data
-- <*> arbitrary -- _wf_lang -- <*> arbitrary -- _wf_lang
......
...@@ -13,6 +13,7 @@ module Main where ...@@ -13,6 +13,7 @@ module Main where
import Gargantext.Prelude import Gargantext.Prelude
import qualified Test.Core.Notifications as Notifications import qualified Test.Core.Notifications as Notifications
import qualified Test.Core.Orchestrator as Orchestrator
import qualified Test.Core.Similarity as Similarity import qualified Test.Core.Similarity as Similarity
import qualified Test.Core.Text.Corpus.Query as CorpusQuery import qualified Test.Core.Text.Corpus.Query as CorpusQuery
import qualified Test.Core.Text.Corpus.TSV as TSVParser import qualified Test.Core.Text.Corpus.TSV as TSVParser
...@@ -75,5 +76,6 @@ main = do ...@@ -75,5 +76,6 @@ main = do
, Worker.tests , Worker.tests
, asyncUpdatesSpec , asyncUpdatesSpec
, Notifications.qcTests , Notifications.qcTests
, Orchestrator.qcTests
, NgramsTerms.tests , NgramsTerms.tests
] ]
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