[refactor] unify Database & ExternalIDs

These types are the same, except for Database.Empty

I managed to have backwards compatibility with the frontend format,
hence the frontend doesn't need any changes.
parent e7b16520
Pipeline #7247 failed with stages
in 20 minutes and 51 seconds
...@@ -13,67 +13,41 @@ module Gargantext.API.Node.Corpus.Types where ...@@ -13,67 +13,41 @@ 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, withObject ) import Data.Aeson ( Value(..), (.:), (.=), withText, object, withObject )
import Data.Aeson.Types (unexpected) import Data.Aeson.Types ( Parser )
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.Database.Action.Flow.Types (DataOrigin(..)) import Gargantext.Database.Action.Flow.Types (DataOrigin(..))
import Gargantext.Prelude import Gargantext.Prelude
import PUBMED.Types qualified as PUBMED
type EPOAPIToken = Text type EPOAPIToken = Text
type EPOAPIUser = Text type EPOAPIUser = Text
data Database = Empty data Database =
| OpenAlex Empty
| PubMed (Maybe PUBMED.APIKey) | DB Types.ExternalAPIs
| Arxiv
| HAL
| IsTex
| Isidore
| EPO (Maybe EPOAPIUser) (Maybe EPOAPIToken)
deriving (Eq, Show, Generic) deriving (Eq, Show, Generic)
instance FromJSON Database where instance FromJSON Database where
parseJSON = withObject "Database" $ \o -> do parseJSON = withObject "Database" $ \o -> do
db <- o .: "db" db <- o .: "db" :: Parser Text
case db of case db of
"Empty" -> pure Empty "Empty" -> pure Empty
"OpenAlex" -> pure OpenAlex _ -> do
"PubMed" -> do eapi <- parseJSON (Object o) :: Parser Types.ExternalAPIs
mAPIKey <- o .:? "api_key" pure $ DB eapi
pure $ PubMed mAPIKey
"Arxiv" -> pure Arxiv
"HAL" -> pure HAL
"IsTex" -> pure IsTex
"Isidore" -> pure Isidore
"EPO" -> do
mAPIUser <- o .:? "api_user"
mAPIToken <- o .:? "api_token"
pure $ EPO mAPIUser mAPIToken
s -> unexpected (String s)
instance ToJSON Database where instance ToJSON Database where
toJSON (PubMed mAPIKey) = object [ "db" .= toJSON ("PubMed" :: Text) toJSON Empty = object [ "db" .= (show Empty :: Text)]
, "api_key" .= toJSON mAPIKey ] toJSON (DB db) = toJSON db
toJSON (EPO mAPIUser mAPIToken) = object [ "db" .= toJSON ("EPO" :: Text)
, "api_user" .= toJSON mAPIUser
, "api_token" .= toJSON mAPIToken ]
toJSON t = object [ "db" .= toJSON (show t :: Text) ]
instance ToSchema Database where instance ToSchema Database where
declareNamedSchema = genericDeclareNamedSchemaUnrestricted defaultSchemaOptions declareNamedSchema = genericDeclareNamedSchemaUnrestricted defaultSchemaOptions
datafield2origin :: Datafield -> DataOrigin datafield2origin :: Datafield -> DataOrigin
datafield2origin (External Empty) = InternalOrigin Types.IsTex datafield2origin (External Empty) = InternalOrigin Types.IsTex
datafield2origin (External OpenAlex) = ExternalOrigin Types.OpenAlex datafield2origin (External (DB db)) = ExternalOrigin db
datafield2origin (External (PubMed mAPIKey)) = ExternalOrigin (Types.PubMed mAPIKey) -- -- | This isn't really used
datafield2origin (External Arxiv) = ExternalOrigin Types.Arxiv datafield2origin _ = InternalOrigin Types.IsTex
datafield2origin (External HAL) = ExternalOrigin Types.HAL
datafield2origin (External IsTex) = ExternalOrigin Types.IsTex
datafield2origin (External Isidore) = ExternalOrigin Types.Isidore
datafield2origin (External (EPO mAPIUser mAPIToken)) = ExternalOrigin (Types.EPO mAPIUser mAPIToken)
-- | This isn't really used
datafield2origin _ = InternalOrigin Types.IsTex
------------------------------------------------------------------------ ------------------------------------------------------------------------
data Datafield = Gargantext data Datafield = Gargantext
......
...@@ -156,11 +156,6 @@ notifyJobKilled env (W.State { name }) (Just bm) = do ...@@ -156,11 +156,6 @@ notifyJobKilled env (W.State { name }) (Just bm) = do
-- | Spawn a worker with PGMQ broker -- | Spawn a worker with PGMQ broker
-- TODO:
-- - reduce size of DB pool
-- - progress report via notifications
-- - I think there is no point to save job result, as usually there is none (we have side-effects only)
-- - replace Servant.Job to use workers instead of garg API threads
withPGMQWorker :: HasWorkerBroker withPGMQWorker :: HasWorkerBroker
=> WorkerEnv => WorkerEnv
-> WorkerDefinition -> WorkerDefinition
......
...@@ -185,7 +185,7 @@ dbEnvSetup ctx = do ...@@ -185,7 +185,7 @@ dbEnvSetup ctx = do
_ <- createAliceAndBob testEnv _ <- createAliceAndBob testEnv
pure ctx pure ctx
-- show the full exceptions during testing, rather than shallowing them under a generic -- show the full exceptions during testing, rather than shallowing them under a generic
-- "Something went wrong". -- "Something went wrong".
showDebugExceptions :: SomeException -> Wai.Response showDebugExceptions :: SomeException -> Wai.Response
......
...@@ -131,13 +131,7 @@ instance Arbitrary FileType where arbitrary = genericArbitrary ...@@ -131,13 +131,7 @@ instance Arbitrary FileType where arbitrary = genericArbitrary
instance Arbitrary CT.Database where instance Arbitrary CT.Database where
arbitrary = oneof [ pure CT.Empty arbitrary = oneof [ pure CT.Empty
, pure CT.OpenAlex , CT.DB <$> arbitrary ]
, CT.PubMed <$> arbitrary
, pure CT.Arxiv
, pure CT.HAL
, pure CT.IsTex
, pure CT.Isidore
, CT.EPO <$> arbitrary <*> arbitrary ]
instance Arbitrary Datafield where arbitrary = genericArbitrary instance Arbitrary Datafield where arbitrary = genericArbitrary
instance Arbitrary WithQuery where arbitrary = genericArbitrary instance Arbitrary WithQuery where arbitrary = genericArbitrary
......
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