Verified Commit 59c23118 authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

Merge branch 'dev' into 238-dev-async-job-worker

parents 494c0541 a0ec337b
## Version 0.0.7.3.1
* [FRONT][FIX][Cannot build the project on latest `dev` (#701)](https://gitlab.iscpif.fr/gargantext/purescript-gargantext/issues/701)
* [FRONT][FIX][Phylomemy panel reload after first query (#674)](https://gitlab.iscpif.fr/gargantext/purescript-gargantext/issues/674)
* [BACK][FIX][Various test failures (#408)](https://gitlab.iscpif.fr/gargantext/haskell-gargantext/issues/408)
* [BACK][FIX][Swagger documentation is down (#407)](https://gitlab.iscpif.fr/gargantext/haskell-gargantext/issues/407)
* [BACK][ADMIN][Improve startup error from
`runDbCheck`](https://gitlab.iscpif.fr/gargantext/haskell-gargantext/merge_requests/347)
* [BACK][CLEAN] removing unused SQL function in schema.sql
* [BACK][TESTS][Terms are calculated over all documents, even those in trash (#385)](https://gitlab.iscpif.fr/gargantext/haskell-gargantext/issues/385)
## Version 0.0.7.3 [/!\ Maintenance command inside]
* [BACK][FIX][Upgrade to GHC 9.4.8][Switch from .ini to TOML? (#304)](https://gitlab.iscpif.fr/gargantext/haskell-gargantext/issues/304)
......
......@@ -404,35 +404,3 @@ FOR EACH ROW
EXECUTE PROCEDURE check_node_stories_json();
CREATE OR REPLACE FUNCTION check_ngrams_json()
RETURNS TRIGGER AS $$
DECLARE
missing_ngrams_exist boolean;
BEGIN
WITH child_ngrams as
(SELECT jsonb_array_elements_text(ngrams_repo_element->'children') AS term
FROM node_stories
WHERE term = OLD.terms),
parent_ngrams AS
(SELECT ngrams_repo_element->>'root' AS term
FROM node_stories
WHERE term = OLD.terms),
child_parent_ngrams AS
(SELECT * FROM child_ngrams
UNION SELECT * FROM parent_ngrams)
SELECT EXISTS(SELECT * FROM child_parent_ngrams) INTO missing_ngrams_exist;
IF missing_ngrams_exist THEN
RAISE EXCEPTION 'ngrams are missing: %', row_to_json(OLD);
END IF;
RETURN OLD;
END;
$$ LANGUAGE plpgsql;
CREATE OR REPLACE TRIGGER check_ngrams_json_trg
AFTER DELETE
ON ngrams
FOR EACH ROW
EXECUTE PROCEDURE check_ngrams_json();
......@@ -5,7 +5,7 @@ cabal-version: 3.4
-- see: https://github.com/sol/hpack
name: gargantext
version: 0.0.7.3
version: 0.0.7.3.1
synopsis: Search, map, share
description: Please see README.md
category: Data
......@@ -34,6 +34,7 @@ data-files:
ekg-assets/cross.png
test-data/ngrams/GarganText_NgramsTerms-QuantumComputing.json
test-data/ngrams/GarganText_DocsList-nodeId-177.json
test-data/ngrams/GarganText_NgramsTerms-nodeId-177.json
test-data/ngrams/simple.json
test-data/ngrams/simple.tsv
test-data/phylo/bpa_phylo_test.json
......@@ -255,6 +256,7 @@ library
Gargantext.Database.Admin.Types.Hyperdata
Gargantext.Database.Admin.Types.Hyperdata.Corpus
Gargantext.Database.Admin.Types.Hyperdata.Document
Gargantext.Database.Admin.Types.Hyperdata.Folder
Gargantext.Database.Admin.Types.Node
Gargantext.Database.Prelude
Gargantext.Database.Query.Facet
......@@ -425,7 +427,6 @@ library
Gargantext.Database.Admin.Types.Hyperdata.Dashboard
Gargantext.Database.Admin.Types.Hyperdata.Default
Gargantext.Database.Admin.Types.Hyperdata.File
Gargantext.Database.Admin.Types.Hyperdata.Folder
Gargantext.Database.Admin.Types.Hyperdata.Frame
Gargantext.Database.Admin.Types.Hyperdata.List
Gargantext.Database.Admin.Types.Hyperdata.Model
......
cradle:
cabal:
- path: "./src"
component: "lib:gargantext"
- path: "./bin/gargantext-cli/Main.hs"
component: "gargantext:exe:gargantext-cli"
- path: "./bin/gargantext-cli/CLI/Admin.hs"
component: "gargantext:exe:gargantext-cli"
- path: "./bin/gargantext-cli/CLI/FileDiff.hs"
component: "gargantext:exe:gargantext-cli"
- path: "./bin/gargantext-cli/CLI/FilterTermsAndCooc.hs"
component: "gargantext:exe:gargantext-cli"
- path: "./bin/gargantext-cli/CLI/Import.hs"
component: "gargantext:exe:gargantext-cli"
- path: "./bin/gargantext-cli/CLI/Ini.hs"
component: "gargantext:exe:gargantext-cli"
- path: "./bin/gargantext-cli/CLI/Init.hs"
component: "gargantext:exe:gargantext-cli"
- path: "./bin/gargantext-cli/CLI/Invitations.hs"
component: "gargantext:exe:gargantext-cli"
- path: "./bin/gargantext-cli/CLI/ObfuscateDB.hs"
component: "gargantext:exe:gargantext-cli"
- path: "./bin/gargantext-cli/CLI/Parsers.hs"
component: "gargantext:exe:gargantext-cli"
- path: "./bin/gargantext-cli/CLI/Phylo.hs"
component: "gargantext:exe:gargantext-cli"
- path: "./bin/gargantext-cli/CLI/Phylo/Common.hs"
component: "gargantext:exe:gargantext-cli"
- path: "./bin/gargantext-cli/CLI/Phylo/Profile.hs"
component: "gargantext:exe:gargantext-cli"
- path: "./bin/gargantext-cli/CLI/Server/Routes.hs"
component: "gargantext:exe:gargantext-cli"
- path: "./bin/gargantext-cli/CLI/Types.hs"
component: "gargantext:exe:gargantext-cli"
- path: "./bin/gargantext-cli/CLI/Upgrade.hs"
component: "gargantext:exe:gargantext-cli"
- path: "./bin/gargantext-cli/Paths_gargantext.hs"
component: "gargantext:exe:gargantext-cli"
- path: "./bin/gargantext-server/Main.hs"
component: "gargantext:exe:gargantext-server"
- path: "./bin/gargantext-server/Paths_gargantext.hs"
component: "gargantext:exe:gargantext-server"
- path: "./test"
component: "gargantext:test:garg-test-tasty"
- path: "./bin/gargantext-cli"
component: "gargantext:test:garg-test-tasty"
- path: "./test"
component: "gargantext:test:garg-test-hspec"
- path: "./bench/Main.hs"
component: "gargantext:bench:garg-bench"
- path: "./bench/Paths_gargantext.hs"
component: "gargantext:bench:garg-bench"
......@@ -92,12 +92,13 @@ startGargantext mode port sf@(SettingsFile settingsFile) = withLoggerHoisted mod
where runDbCheck env = do
r <- runExceptT (runReaderT DB.dbCheck env) `catch`
(\(_ :: SomeException) -> pure $ Right False)
(\(err :: SomeException) -> pure $ Left err)
case r of
Right True -> pure ()
_ -> panicTrace $
"You must run 'gargantext-init " <> pack settingsFile <>
Right True -> pure ()
Right False -> panicTrace $
"You must run 'gargantext-cli init " <> pack settingsFile <>
"' before running gargantext-server (only the first time)."
Left err -> panicTrace $ "Unexpected exception:" <> show err
oneHour = Clock.fromNanoSecs 3600_000_000_000
portRouteInfo :: NotificationsConfig -> PortNumber -> MicroServicesProxyStatus -> IO ()
......
......@@ -14,9 +14,10 @@ Portability : POSIX
module Gargantext.Core.Viz.Graph.Types
where
import Data.Aeson (defaultOptions)
import Data.HashSet (HashSet)
import Data.HashSet qualified as HashSet
import Data.Swagger (ToSchema(..), genericDeclareNamedSchema)
import Data.Swagger (ToSchema(..), genericDeclareNamedSchema, defaultSchemaOptions)
import Data.Text (pack)
import Database.PostgreSQL.Simple.FromField (FromField(..))
import Gargantext.API.Ngrams.Types (NgramsTerm)
......@@ -245,9 +246,9 @@ instance FromField HyperdataGraphAPI
data GraphLegendAPI = GraphLegendAPI [LegendField]
deriving (Show, Generic)
$(deriveJSON (unPrefix "_graphAPI") ''GraphLegendAPI)
$(deriveJSON defaultOptions ''GraphLegendAPI)
instance ToSchema GraphLegendAPI where
declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_graphAPI")
declareNamedSchema = genericDeclareNamedSchema defaultSchemaOptions
makeLenses ''GraphLegendAPI
......
......@@ -58,5 +58,6 @@
},
"hash": ""
}
]
],
"garg_version": "0.0.7.1.16"
}
{ "NgramsTerms":{ "version":1 ,"data":{ "fortran":{"size":2,"list":"MapTerm","children":[]} } }
}
......@@ -8,24 +8,31 @@ module Test.API.Routes where
import Data.Text.Encoding qualified as TE
import Fmt (Builder, (+|), (|+))
import Gargantext.API.Admin.Auth.Types (AuthRequest, AuthResponse, Token)
import Gargantext.API.Admin.Orchestrator.Types (JobLog, asyncJobsAPI')
import Gargantext.API.Errors
import Gargantext.API.HashedResponse (HashedResponse)
import Gargantext.API.Ngrams.Types ( NgramsTable, NgramsTablePatch, OrderBy, TabType, Versioned, VersionedWithCount )
import Gargantext.API.Routes.Named
import Gargantext.API.Routes.Named.Node
import Gargantext.API.Routes.Named.Private hiding (tableNgramsAPI)
import Gargantext.API.Routes.Named.Table
import Gargantext.API.Types () -- MimeUnrender instances
import Gargantext.Core.Types (ListId, NodeId)
import Gargantext.Core.Text.Corpus.Query (RawQuery)
import Gargantext.Core.Types (ListId, NodeId, NodeType, NodeTableResult)
import Gargantext.Core.Types.Main (ListType)
import Gargantext.Core.Types.Query (Limit, MaxSize, MinSize, Offset)
import Gargantext.Database.Admin.Types.Hyperdata
import Gargantext.Database.Query.Facet qualified as Facet
import Gargantext.Prelude
import Network.HTTP.Types qualified as H
import Network.Wai.Handler.Warp (Port)
import Servant ((:<|>)(..))
import Servant.API.WebSocket qualified as WS
import Servant.Auth.Client qualified as S
import Servant.Client (ClientM)
import Servant.Client.Core (RunClient, HasClient(..), Request)
import Servant.Client.Generic ( genericClient, AsClientT )
import Servant.Job.Async
instance RunClient m => HasClient m WS.WebSocketPending where
......@@ -47,6 +54,9 @@ mkUrl :: Port -> Builder -> ByteString
mkUrl _port urlPiece =
"/api/" +| curApi |+ urlPiece
gqlUrl :: ByteString
gqlUrl = "/gql"
-- | The client for the full API. It also serves as a \"proof\" that our
-- whole API has all the required instances to be used in a client.
......@@ -64,19 +74,44 @@ auth_api = clientRoutes & apiWithCustomErrorScheme
& gargAuthAPI
& authEp
table_ngrams_get_api :: Token
-> NodeId
-> TabType
-> ListId
-> Limit
-> Maybe Offset
-> Maybe ListType
-> Maybe MinSize
-> Maybe MaxSize
-> Maybe OrderBy
-> Maybe Text
-> ClientM (VersionedWithCount NgramsTable)
table_ngrams_get_api (toServantToken -> token) nodeId =
toServantToken :: Token -> S.Token
toServantToken = S.Token . TE.encodeUtf8
update_node :: Token
-> NodeId
-> UpdateNodeParams
-> ClientM (JobStatus 'Safe JobLog)
update_node (toServantToken -> token) nodeId params =
clientRoutes & apiWithCustomErrorScheme
& ($ GES_new)
& backendAPI
& backendAPI'
& mkBackEndAPI
& gargAPIVersion
& gargPrivateAPI
& mkPrivateAPI
& ($ token)
& nodeEp
& nodeEndpointAPI
& ($ nodeId)
& updateAPI
& updateNodeEp
& asyncJobsAPI'
& (\(_ :<|> submitForm :<|> _) -> submitForm (JobInput params Nothing))
get_table_ngrams :: Token
-> NodeId
-> TabType
-> ListId
-> Limit
-> Maybe Offset
-> Maybe ListType
-> Maybe MinSize
-> Maybe MaxSize
-> Maybe OrderBy
-> Maybe Text
-> ClientM (VersionedWithCount NgramsTable)
get_table_ngrams (toServantToken -> token) nodeId =
clientRoutes & apiWithCustomErrorScheme
& ($ GES_new)
& backendAPI
......@@ -93,16 +128,13 @@ table_ngrams_get_api (toServantToken -> token) nodeId =
& tableNgramsGetAPI
& getNgramsTableEp
toServantToken :: Token -> S.Token
toServantToken = S.Token . TE.encodeUtf8
table_ngrams_put_api :: Token
-> NodeId
-> TabType
-> ListId
-> Versioned NgramsTablePatch
-> ClientM (Versioned NgramsTablePatch)
table_ngrams_put_api (toServantToken -> token) nodeId =
put_table_ngrams :: Token
-> NodeId
-> TabType
-> ListId
-> Versioned NgramsTablePatch
-> ClientM (Versioned NgramsTablePatch)
put_table_ngrams (toServantToken -> token) nodeId =
clientRoutes & apiWithCustomErrorScheme
& ($ GES_new)
& backendAPI
......@@ -118,3 +150,51 @@ table_ngrams_put_api (toServantToken -> token) nodeId =
& tableNgramsAPI
& tableNgramsPutAPI
& putNgramsTableEp
get_table :: Token
-> NodeId
-> Maybe TabType
-> Maybe Limit
-> Maybe Offset
-> Maybe Facet.OrderBy
-> Maybe RawQuery
-> Maybe Text
-> ClientM (HashedResponse FacetTableResult)
get_table (toServantToken -> token) nodeId =
clientRoutes & apiWithCustomErrorScheme
& ($ GES_new)
& backendAPI
& backendAPI'
& mkBackEndAPI
& gargAPIVersion
& gargPrivateAPI
& mkPrivateAPI
& ($ token)
& nodeEp
& nodeEndpointAPI
& ($ nodeId)
& tableAPI
& getTableEp
get_children :: Token
-> NodeId
-> Maybe NodeType
-> Maybe Offset
-> Maybe Limit
-> ClientM (NodeTableResult HyperdataAny)
get_children (toServantToken -> token) nodeId =
clientRoutes & apiWithCustomErrorScheme
& ($ GES_new)
& backendAPI
& backendAPI'
& mkBackEndAPI
& gargAPIVersion
& gargPrivateAPI
& mkPrivateAPI
& ($ token)
& nodeEp
& nodeEndpointAPI
& ($ nodeId)
& childrenAPI
& summaryChildrenEp
This diff is collapsed.
......@@ -7,33 +7,38 @@ module Test.Utils where
import Control.Exception.Safe ()
import Control.Monad ()
import Data.Aeson qualified as JSON
import Data.Aeson.KeyMap qualified as KM
import Data.Aeson qualified as JSON
import Data.ByteString.Char8 qualified as B
import Data.ByteString.Lazy qualified as L
import Data.Map.Strict qualified as Map
import Data.Text qualified as T
import Data.Text.Encoding qualified as TE
import Data.Text.Lazy qualified as TL
import Data.Text.Lazy.Encoding qualified as TLE
import Data.Text.Lazy qualified as TL
import Data.Text qualified as T
import Data.TreeDiff
import Fmt (Builder)
import Gargantext.API.Routes.Types (xGargErrorScheme)
import Gargantext.API.Admin.Auth.Types (AuthRequest(..), Token, authRes_token)
import Gargantext.API.Admin.Orchestrator.Types
import Gargantext.API.Routes.Types (xGargErrorScheme)
import Gargantext.Core.Types.Individu (Username, GargPassword)
import Gargantext.Prelude
import Network.HTTP.Client (defaultManagerSettings, newManager)
import Network.HTTP.Types (Header, Method, status200)
import Network.HTTP.Client qualified as HTTP
import Network.HTTP.Types.Header (hAccept, hAuthorization, hContentType)
import Network.HTTP.Types (Header, Method, status200)
import Network.Wai.Handler.Warp (Port)
import Network.Wai.Test (SResponse(..))
import Prelude qualified
import Servant.Client (ClientEnv, baseUrlPort, mkClientEnv, parseBaseUrl, runClientM)
import Servant.Client (ClientEnv, baseUrlPort, mkClientEnv, parseBaseUrl, runClientM, makeClientRequest, defaultMakeClientRequest)
import Servant.Client.Core (BaseUrl)
import Servant.Client.Core.Request qualified as Client
import System.Environment (lookupEnv)
import System.Timeout qualified as Timeout
import Test.API.Routes (auth_api, mkUrl)
import Test.Hspec.Expectations
import Test.Hspec.Wai (MatchBody(..), WaiExpectation, WaiSession, request)
import Test.Hspec.Wai.JSON (FromValue(..))
import Test.Hspec.Wai (MatchBody(..), WaiExpectation, WaiSession, request)
import Test.Hspec.Wai.Matcher (MatchHeader(..), ResponseMatcher(..), bodyEquals, formatHeader, match)
import Test.Tasty.HUnit (Assertion, assertBool)
import Test.Types
......@@ -183,12 +188,27 @@ withValidLogin port ur pwd act = do
case result of
Left err -> liftIO $ throwIO $ Prelude.userError (show err)
Right res -> do
traceEnabled <- isJust <$> liftIO (lookupEnv "GARG_DEBUG_LOGS")
let token = res ^. authRes_token
act clientEnv0 token
act (clientEnv0 { makeClientRequest = gargMkRequest traceEnabled }) token
-- | Allows to enable/disable logging of the input 'Request' to check what the
-- client is actually sending to the server.
-- FIXME(adn) We cannot upgrade to servant-client 0.20 due to OpenAlex:
-- https://gitlab.iscpif.fr/gargantext/crawlers/openalex/blob/main/src/OpenAlex/ServantClientLogging.hs#L24
gargMkRequest :: Bool -> BaseUrl -> Client.Request -> HTTP.Request
gargMkRequest traceEnabled bu clientRq =
let httpReq = defaultMakeClientRequest bu clientRq
in case traceEnabled of
True ->
traceShowId httpReq
False -> httpReq
-- | Poll the given job URL every second until it finishes.
-- Retries up to 60 times (i.e. for 1 minute, before giving up)
-- /NOTE(adn)/: Check the content of the \"events\" logs as a stopgap
-- measure for #390.
pollUntilFinished :: HasCallStack
=> Token
-> Port
......@@ -208,7 +228,15 @@ pollUntilFinished tkn port mkUrlPiece = go 60
| _jph_status h == "IsFailure"
-> panicTrace $ "JobPollHandle contains a failure: " <> TE.decodeUtf8 (L.toStrict $ JSON.encode h)
| otherwise
-> pure h
-> case any hasError (_jph_log h) of
True -> panicTrace $ "JobPollHandle contains a failure: " <> TE.decodeUtf8 (L.toStrict $ JSON.encode h)
False -> pure h
-- FIXME(adn) This is wrong, errs should be >= 1.
hasError :: JobLog -> Bool
hasError JobLog{..} = case _scst_failed of
Nothing -> False
Just errs -> errs > 1
-- | Like HUnit's '@?=', but With a nicer error message in case the two entities are not equal.
(@??=) :: (HasCallStack, ToExpr a, Eq a) => a -> a -> Assertion
......
......@@ -367,23 +367,30 @@ testMarkProgress = do
myEnv <- newTestEnv
-- evts <- newTBQueueIO 7
evts <- newTVarIO []
let expectedEvents = 7
let getStatus hdl = do
liftIO $ threadDelay 100_000
st <- getLatestJobStatus hdl
-- liftIO $ atomically $ writeTBQueue evts st
liftIO $ atomically $ modifyTVar evts (\xs -> xs ++ [st])
readAllEvents = do
readAllEvents = do
-- We will get thread blocking if there is ANY error in the job
-- Hence we assert the `readAllEvents` test doesn't take too long
mRet <- timeout 1_000_000 $ atomically $ do
mRet <- timeout 5_000_000 $ atomically $ do
-- allEventsArrived <- isFullTBQueue evts
evts' <- readTVar evts
-- STM retry if things failed
-- check allEventsArrived
check (length evts' == 7)
check (length evts' == expectedEvents)
-- flushTBQueue evts
return evts'
return $ fromMaybe [] mRet
pure evts'
case mRet of
Nothing -> Prelude.fail $ "testMarkProgress: timeout exceeded, but didn't receive all 7 required events."
Just xs
| length xs == expectedEvents
-> pure xs
| otherwise
-> Prelude.fail $ "testMarkProgress: received some events, but they were not of the expected number (" <> show expectedEvents <> "): " <> show xs
withJob_ myEnv $ \hdl _input -> do
markStarted 10 hdl
......@@ -410,6 +417,8 @@ testMarkProgress = do
getStatus hdl
evts' <- readAllEvents
-- This pattern match should never fail, because the precondition is
-- checked in 'readAllEvents'.
let [jl0, jl1, jl2, jl3, jl4, jl5, jl6] = evts'
-- Check the events are what we expect
......
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