Commit eedac139 authored by Alfredo Di Napoli's avatar Alfredo Di Napoli

Check we can retrieve the ngrams

parent 924501bf
......@@ -444,6 +444,7 @@ library
, fgl ^>= 5.7.0.3
, filelock ^>= 0.1.1.5
, filepath ^>= 1.4.2.1
, fmt
, formatting ^>= 7.1.3
, full-text-search ^>= 0.2.1.4
, fullstop ^>= 0.1.4
......
......@@ -35,6 +35,7 @@ import Data.Time (UTCTime)
import Database.PostgreSQL.Simple.FromField (FromField, fromField, fromJSONField)
import Database.PostgreSQL.Simple.ToField (ToField, toField, toJSONField)
import Database.PostgreSQL.Simple.ToRow (ToRow, toRow)
import Fmt
import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixSwagger, wellNamedSchema)
import Gargantext.Database.Schema.Context
import Gargantext.Database.Schema.Node
......@@ -250,6 +251,9 @@ newtype NodeId = UnsafeMkNodeId { _NodeId :: Int }
instance ResourceId NodeId where
isPositive = (> 0) . _NodeId
instance Buildable NodeId where
build (UnsafeMkNodeId nid) = build nid
instance GQLType NodeId
instance Prelude.Show NodeId where
show (UnsafeMkNodeId n) = "nodeId-" <> show n
......
......@@ -85,9 +85,8 @@ protectedNewError tkn mth url = protectedWith newErrorFormat tkn mth url
where
newErrorFormat = [(CI.mk "X-Garg-Error-Scheme", "new")]
getJSON :: ByteString -> WaiSession () SResponse
getJSON url =
request "GET" url [(hContentType, "application/json")] ""
getJSON :: Token -> ByteString -> WaiSession () SResponse
getJSON tkn url = protectedWith mempty tkn "GET" url ""
postJSONUrlEncoded :: forall a. (JSON.FromJSON a, Typeable a)
=> Token
......
......@@ -3,6 +3,7 @@
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE NumericUnderscores #-}
{-# LANGUAGE ViewPatterns #-}
module Test.API.UpdateList (
tests
......@@ -28,19 +29,21 @@ import Gargantext.Prelude hiding (get)
import Network.Wai.Handler.Warp qualified as Wai
import Paths_gargantext (getDataFileName)
import Prelude (error)
import Test.API.Private (withValidLogin, protectedJSON, postJSONUrlEncoded)
import Test.API.Private (withValidLogin, protectedJSON, postJSONUrlEncoded, getJSON)
import Test.API.Setup (withTestDBAndPort, setupEnvironment, mkUrl, createAliceAndBob)
import Test.Database.Types
import Test.Hspec
import Test.Hspec.Wai.Internal (withApplication, WaiSession)
import Test.Utils (shouldRespondWith')
import Web.FormUrlEncoded
import Test.Hspec.Wai.JSON (json)
data JobPollHandle = JobPollHandle {
_jph_id :: !Text
, _jph_log :: [JobLog]
, _jph_status :: !Text
, _jph_error :: !(Maybe Text)
}
} deriving Show
instance JSON.FromJSON JobPollHandle where
parseJSON = JSON.withObject "JobPollHandle" $ \o -> do
......@@ -78,7 +81,11 @@ pollUntilFinished tkn port mkUrlPiece = go 60
liftIO $ threadDelay 1_000_000
h' <- protectedJSON tkn "GET" (mkUrl port $ mkUrlPiece h) ""
go (n-1) h'
False -> pure h
False
| _jph_status h == "IsFailure"
-> error $ T.unpack $ "JobPollHandle contains a failure: " <> T.decodeUtf8 (BL.toStrict $ JSON.encode h)
| otherwise
-> pure h
tests :: Spec
tests = sequential $ aroundAll withTestDBAndPort $ do
......@@ -105,3 +112,20 @@ tests = sequential $ aroundAll withTestDBAndPort $ do
(j :: JobPollHandle) <- postJSONUrlEncoded token (mkUrl port url) (urlEncodeFormStable $ toForm jsonFileFormData)
j' <- pollUntilFinished token port mkPollUrl j
liftIO (_jph_status j' `shouldBe` "IsFinished")
-- Now check that we can retrieve the ngrams
let getUrl = "/node/" +| listId |+ "/ngrams?ngramsType=Terms&listType=MapTerm&list="+| listId |+"&limit=50"
getJSON token (mkUrl port getUrl)
`shouldRespondWith'` [json| { "version": 0,
"count": 1,
"data": [
{
"ngrams": "abelian group",
"size": 2,
"list": "MapTerm",
"occurrences": [],
"children": []
}
]
} |]
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