Commit d24ec87a authored by Alexandre Delanoë's avatar Alexandre Delanoë

[TEST] fixing the tests : ok

parent 46dd884f
import Data.Gargantext.Types.Main (Language(..))
import Gargantext.Types.Main (Language(..))
--import qualified Ngrams.Lang.Fr as Fr
import qualified Ngrams.Lang as Lang
import qualified Ngrams.Lang.Occurrences as Occ
......
module Ngrams.Lang where
import Data.Gargantext.Types.Main (Language(..))
import Gargantext.Types.Main (Language(..))
import qualified Ngrams.Lang.Fr as Fr
import qualified Ngrams.Lang.En as En
......
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE NoImplicitPrelude #-}
module Ngrams.Lang.En where
import Test.Hspec
import Data.Gargantext.Prelude
import Data.Gargantext.Types.Main (Language(..))
import Data.Gargantext.Ngrams.Parser (extractNgrams, selectNgrams)
import Gargantext.Prelude
import Gargantext.Types.Main (Language(..))
import Gargantext.Ngrams.Parser (extractNgrams, selectNgrams)
import Data.Text (Text(..))
import Data.List ((!!))
ngramsExtractionTest :: IO ()
ngramsExtractionTest = hspec $ do
describe "Ngrams extraction in English Language" $ do
let textTest = [ "Alcoholic extract of Kaempferia galanga was tested for analgesic and antiinflammatory activities in animal models. ", "Three doses, 300 mg/kg, 600 mg/kg and 1200 mg/kg of the plant extract prepared as a suspension in 2 ml of 2% gum acacia were used. ", " Acute and sub acute inflammatory activities were studied in rats by carrageenan induced paw edema and cotton pellet induced granuloma models respectively. ", "In both models, the standard drug used was aspirin 100 mg/kg. ", "Two doses 600 mg/kg and 1200 mg/kg of plant extract exhibited significant (P<0.001) antiinflammatory activity in carrageenan model and cotton pellet granuloma model in comparison to control. ", "Analgesic activity was studied in rats using hot plate and tail-flick models. ", "Codeine 5 mg/kg and vehicle served as standard and control respectively. ", "The two doses of plant extract exhibited significant analgesic activity in tail flick model (P<0.001) and hot plate model (P<0.001) in comparison to control. ", "In conclusion K. galanga possesses antiinflammatory and analgesic activities. "] :: [String]
let textTest = [ "Alcoholic extract of Kaempferia galanga was tested for analgesic and antiinflammatory activities in animal models. ", "Three doses, 300 mg/kg, 600 mg/kg and 1200 mg/kg of the plant extract prepared as a suspension in 2 ml of 2% gum acacia were used. ", " Acute and sub acute inflammatory activities were studied in rats by carrageenan induced paw edema and cotton pellet induced granuloma models respectively. ", "In both models, the standard drug used was aspirin 100 mg/kg. ", "Two doses 600 mg/kg and 1200 mg/kg of plant extract exhibited significant (P<0.001) antiinflammatory activity in carrageenan model and cotton pellet granuloma model in comparison to control. ", "Analgesic activity was studied in rats using hot plate and tail-flick models. ", "Codeine 5 mg/kg and vehicle served as standard and control respectively. ", "The two doses of plant extract exhibited significant analgesic activity in tail flick model (P<0.001) and hot plate model (P<0.001) in comparison to control. ", "In conclusion K. galanga possesses antiinflammatory and analgesic activities. "] :: [Text]
it "\"Of\" seperates two ngrams" $ do
t1 <- pm (selectNgrams EN) <$> extractNgrams EN (textTest !! 0)
t1 <- map (selectNgrams EN) <$> extractNgrams EN (textTest !! 0)
t1 `shouldBe` [[("Alcoholic extract of Kaempferia galanga","NN","O"),("analgesic activities","NN+CC","O"),("antiinflammatory activities","NN+CC","O"),("animal models","NN","O")]]
it "Tests the conjunction of coordination in two ngrams with its adjectives" $ do
t2 <- pm (selectNgrams EN) <$> extractNgrams EN (textTest !! 2)
t2 <- map (selectNgrams EN) <$> extractNgrams EN (textTest !! 2)
t2 `shouldBe` [[("Acute activities","NN+CC","O"),("sub acute inflammatory activities","NN+CC","O"),("rats","NNS","O"),("carrageenan","NN","O"),("paw edema","NN","O"),("cotton pellet","NN","O"),("granuloma models","NN","O")]]
it "Tests nouns with preposition and determinants" $ do
let t = "Donald Trump is president of the United-States of America."
t2 <- pm (selectNgrams EN) <$> extractNgrams EN t
t2 <- map (selectNgrams EN) <$> extractNgrams EN t
t2 `shouldBe` [[("Donald Trump","NNP","PERSON"),("president of the United-States of America","NN","LOCATION")]]
......
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE NoImplicitPrelude #-}
module Ngrams.Lang.Fr where
import Test.Hspec
import Data.Gargantext.Prelude
import Data.Gargantext.Types.Main (Language(..))
import Data.Gargantext.Ngrams.Parser (extractNgrams, selectNgrams)
import Gargantext.Prelude
import Gargantext.Types.Main (Language(..))
import Gargantext.Ngrams.Parser (extractNgrams, selectNgrams)
ngramsExtractionTest :: IO ()
ngramsExtractionTest = hspec $ do
describe "Behavioral tests: ngrams extraction in French Language" $ do
it "Groupe : adjectif et nom commun" $ do
let textFr = "Le beau texte fut écrit."
testFr <- pm (selectNgrams FR) <$> (extractNgrams FR) textFr
testFr <- map (selectNgrams FR) <$> (extractNgrams FR) textFr
testFr `shouldBe` [[("beau texte","NC","O")]]
it "Groupe : adjectifs et nom commun" $ do
let textFr = "Le beau petit texte fut écrit."
testFr <- pm (selectNgrams FR) <$> (extractNgrams FR) textFr
testFr <- map (selectNgrams FR) <$> (extractNgrams FR) textFr
testFr `shouldBe` [[("beau petit texte","NC","O")]]
-- `shouldBe` [[("beau texte","NC","O"),("petit texte","NC","O")]] ?
it "Groupe : nom commun et adjectif" $ do
let textFr = "Le livre blanc fut écrit."
testFr <- pm (selectNgrams FR) <$> (extractNgrams FR) textFr
testFr <- map (selectNgrams FR) <$> (extractNgrams FR) textFr
testFr `shouldBe` [[("livre blanc","NC","O")]]
it "Groupe : nom commun et adjectifs avec conjonction" $ do
let textFr = "Le livre blanc et rouge."
testFr <- pm (selectNgrams FR) <$> (extractNgrams FR) textFr
testFr <- map (selectNgrams FR) <$> (extractNgrams FR) textFr
testFr `shouldBe` [[("livre blanc","N","O"),("livre rouge","N","O")]]
-- `shouldBe` [[("livre blanc et rouge","N","O")]] ?
it "Groupe: Nom commun + préposition + Nom commun" $ do
let textFr0 = "Le problème du jour est résolu."
testFr0 <- pm (selectNgrams FR) <$> (extractNgrams FR) textFr0
testFr0 <- map (selectNgrams FR) <$> (extractNgrams FR) textFr0
testFr0 `shouldBe` [[("problème du jour","NC","O")]]
it "Groupe: Nom commun + préposition + déterminant + Nom commun" $ do
let textFr0 = "Emmanuel Macron est le président de la France."
testFr0 <- pm (selectNgrams FR) <$> (extractNgrams FR) textFr0
testFr0 <- map (selectNgrams FR) <$> (extractNgrams FR) textFr0
testFr0 `shouldBe` [[("Emmanuel Macron","NPP","PERSON"),("président de la France","NC","LOCATION")]]
it "Groupe: Nom commun + préposition + Nom commun + prép + Nom commun" $ do
let textFr1 = "L'heure d'arrivée des coureurs dépend de la météo du jour."
testFr1 <- pm (selectNgrams FR) <$> (extractNgrams FR) textFr1
testFr1 <- map (selectNgrams FR) <$> (extractNgrams FR) textFr1
testFr1 `shouldBe` [[("heure d' arrivée des coureurs","NC","O"),("météo du jour","NC","O")]]
......@@ -9,11 +9,11 @@ import Control.Exception (evaluate)
import Data.Text (Text)
import Data.Gargantext.Prelude
import Data.Gargantext.Types.Main (Language(..))
import Data.Gargantext.Ngrams
import Data.Gargantext.Ngrams.Occurrences (parseOccurrences)
import Data.Gargantext.Ngrams.Parser (extractNgrams, selectNgrams)
import Gargantext.Prelude
import Gargantext.Types.Main (Language(..))
import Gargantext.Ngrams
import Gargantext.Ngrams.Occurrences (parseOccurrences)
import Gargantext.Ngrams.Parser (extractNgrams, selectNgrams)
parsersTest = hspec $ do
......
......@@ -4,9 +4,9 @@
module Ngrams.Metrics (main) where
import Gargantext.Ngrams.Metrics
import Data.Ratio
import Data.Text (Text)
import Data.Gargantext.Ngrams.Metrics
import Test.Hspec
import Test.QuickCheck
import qualified Data.Text as T
......
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