Commit 893b4cf8 authored by Yoelis Acourt's avatar Yoelis Acourt

fix(ngrams): occurences counting with quotes

parent 163304df
Pipeline #6864 failed with stages
in 48 minutes and 39 seconds
......@@ -836,7 +836,8 @@ test-suite garg-test-tasty
Test.Server.ReverseProxy
Test.Types
Test.Utils
Test.Utils.Crypto
Test.Utils.Crypto
Test.Ngrams.Lang.Occurrences
Test.Utils.Jobs
hs-source-dirs:
test bin/gargantext-cli
......
......@@ -33,7 +33,7 @@ words = monoTexts
-- | Sentence split separators
isSep :: Char -> Bool
isSep = (`elem` (",.:;?!(){}[]\"\'" :: String))
isSep = (`elem` (",.:;?!(){}[]" :: String))
monoTerms :: Lang -> Text -> [TermsWithCount]
monoTerms l txt = map (\t -> (monoText2term l t, 1)) $ monoTexts txt
......
......@@ -14,7 +14,28 @@ commentary with @some markup@.
{-# LANGUAGE ScopedTypeVariables #-}
module Test.Ngrams.Lang.Occurrences where
import Test.Hspec
import Data.Either
import Gargantext.Core.Text.Terms.WithList
import Gargantext.Core (Lang(ZH, EN))
import Gargantext.Prelude
test :: Spec
test = do
describe "terms in text counting" $ do
it "words with quotes should match" $ do
let ngrams = ["j'aime"]
let doc = "j'aime"
let output = []
termsInText EN (buildPatternsWith EN ngrams) doc `shouldBe` [("j'aime", 1)]
-- it "words with quotes should match and be case sentive" $ do
-- let ngrams = ["j'aIme"]
-- let doc = "j'aime"
-- let output = []
-- termsInText EN (buildPatternsWith EN ngrams) doc `shouldNotBe` [("j'aime", 1)]
{-
import Test.Hspec
......
......@@ -27,6 +27,7 @@ import qualified Test.Utils.Crypto as Crypto
import qualified Test.Utils.Jobs as Jobs
import qualified Test.Core.Similarity as Similarity
import qualified Test.Core.AsyncUpdates as AsyncUpdates
import qualified Test.Ngrams.Lang.Occurrences as Occurrences
import Test.Tasty
import Test.Tasty.Hspec
......@@ -41,6 +42,7 @@ main = do
jobsSpec <- testSpec "Jobs" Jobs.test
similaritySpec <- testSpec "Similarity" Similarity.test
asyncUpdatesSpec <- testSpec "AsyncUpdates" AsyncUpdates.test
occurrencesSepc <- testSpec "AsyncUpdates" Occurrences.test
defaultMain $ testGroup "Gargantext"
[ utilSpec
......@@ -49,6 +51,7 @@ main = do
, cryptoSpec
, nlpSpec
, jobsSpec
, occurrencesSepc
, NgramsQuery.tests
, CorpusQuery.tests
, TSVParser.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