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

[TESTS][FIX] No Implicit Prelude for Tests too.

parent 644a7a89
......@@ -149,6 +149,8 @@ tests:
garg-test:
main: Main.hs
source-dirs: src-test
default-extensions:
- NoImplicitPrelude
ghc-options:
- -threaded
- -rtsopts
......
{-|
Module : Main.hs
Description : Main for Gargantext Tests
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
import Gargantext.Prelude
import Gargantext.Types.Main (Language(..))
--import qualified Ngrams.Lang.Fr as Fr
import qualified Ngrams.Lang as Lang
......
module Ngrams.Lang where
import Gargantext.Prelude (IO())
import Gargantext.Types.Main (Language(..))
import qualified Ngrams.Lang.Fr as Fr
......
......@@ -4,14 +4,15 @@
module Ngrams.Lang.En where
import Data.List ((!!))
import Data.Text (Text)
import Test.Hspec
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
......
......@@ -4,18 +4,13 @@
module Ngrams.Lang.Occurrences where
import Test.Hspec
import Control.Exception (evaluate)
import Data.Text (Text)
import Data.Either (Either(Right))
import Gargantext.Prelude
import Gargantext.Types.Main (Language(..))
import Gargantext.Ngrams
import Gargantext.Ngrams.Occurrences (parseOccurrences)
import Gargantext.Ngrams.Parser (extractNgrams, selectNgrams)
parsersTest :: IO ()
parsersTest = hspec $ do
describe "Parser for occurrences" $ do
......
......@@ -4,12 +4,15 @@
module Ngrams.Metrics (main) where
import Gargantext.Ngrams.Metrics
import Data.Ratio
import Data.Text (Text)
import Data.Text (Text)
import qualified Data.Text as T
import Data.Ratio
import Test.Hspec
import Test.QuickCheck
import qualified Data.Text as T
import Gargantext.Prelude
import Gargantext.Ngrams.Metrics
#if !MIN_VERSION_base(4,8,0)
import Control.Applicative
......@@ -121,5 +124,5 @@ testPair :: (Eq a, Show a)
-> Text -- ^ Second input
-> a -- ^ Expected result
-> SpecWith ()
testPair f a b r = it ("‘" ++ T.unpack a ++ "’ and ‘" ++ T.unpack b ++ "’") $
testPair f a b r = it ("‘" <> T.unpack a <> "’ and ‘" <> T.unpack b <> "’") $
f a b `shouldBe` r
......@@ -9,7 +9,6 @@ import Test.QuickCheck
import Parsers.Types
import Control.Applicative ((<*>))
import Data.Tuple (uncurry)
import Data.Either (Either(..))
import Data.Time (ZonedTime(..))
import Data.Text (pack, Text)
......
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE StandaloneDeriving #-}
module Parsers.Types where
import Gargantext.Prelude
import Prelude (floor, fromIntegral)
import Test.QuickCheck
import Test.QuickCheck.Instances ()
......@@ -18,7 +18,7 @@ import Data.Either (Either(..))
deriving instance Eq ZonedTime
looseTimeOfDayPrecision :: TimeOfDay -> TimeOfDay
looseTimeOfDayPrecision (TimeOfDay h m s) = TimeOfDay h m 0
looseTimeOfDayPrecision (TimeOfDay h m _) = TimeOfDay h m 0
looseLocalTimePrecision :: LocalTime -> LocalTime
looseLocalTimePrecision (LocalTime ld ltd) = LocalTime ld $ looseTimeOfDayPrecision ltd
......
module Gargantext.Analysis where
{-|
Module : Gargantext.Analysis
Description : Gargantext Analysis
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
import Gargantext.Prelude
{-# LANGUAGE NoImplicitPrelude #-}
module Gargantext.Analysis
where
import Gargantext.Prelude (undefined, IO(), Int())
-- import qualified Data.Text.Lazy as DTL
import Data.Text
......
......@@ -46,7 +46,7 @@ average x = L.sum x / L.genericLength x
average' :: [Int] -> Double
average' x = (L.sum y) / (L.genericLength y) where
y = map fromIntegral x
y = L.map fromIntegral x
countYear :: [Integer] -> Map Integer Integer
......
......@@ -24,7 +24,8 @@ import Protolude ( Bool(True, False), Int, Double, Integer
, sum, fromIntegral, length, fmap
, takeWhile, sqrt, undefined, identity
, abs, maximum, minimum, return, snd, truncate
, (+), (*), (/), (-), (.), (>=), ($), (**), (^), (<), (>), (==), (<>)
, (+), (*), (/), (-), (.), (>=), ($), (**), (^), (<), (>)
, Eq, (==), (<>)
, (&&), (||), not
, toS
)
......
{-|
Module : Gargantext.
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
{-# LANGUAGE NoImplicitPrelude #-}
module Gargantext.RCT where
import Gargantext.Prelude
......@@ -51,4 +64,3 @@ foo = undefined
-- forms = words
......@@ -21,22 +21,21 @@ commentary with @some markup@.
module Gargantext.Types.Main where
------------------------------------------------------------------------
import Prelude
import Protolude (fromMaybe)
import Data.Maybe (fromMaybe)
import Data.Eq (Eq())
import Data.Monoid ((<>))
import Data.Text (Text)
import Data.Text (Text, pack)
import Data.List (lookup)
import Gargantext.Types.Node
import Gargantext.Prelude
------------------------------------------------------------------------
------------------------------------------------------------------------
-- | Language of a Text
-- For simplicity, we suppose text has an homogenous language
data Language = EN | FR -- | DE | IT | SP
data Language = EN | FR
-- | DE | IT | SP
-- > EN == english
-- > FR == french
-- > DE == deutch (not implemented yet)
......@@ -44,11 +43,9 @@ data Language = EN | FR -- | DE | IT | SP
-- > SP == spanish (not implemented yet)
-- > ... add your language and help us to implement it (:
-- All the Database is structred like a hierarchical Tree
data Tree a = NodeT a [Tree a]
deriving (Show, Read, Eq)
deriving (Show, Read, Eq)
-- data Tree a = NodeT a [Tree a]
-- same as Data.Tree
......@@ -161,19 +158,16 @@ nodeTypes = [ (NodeUser , 1)
]
--
nodeTypeId :: NodeType -> NodeTypeId
nodeTypeId tn = fromMaybe (error $ "Typename " <> show tn <> " does not exist")
nodeTypeId tn = fromMaybe (panic $ pack $ "Typename " <> show tn <> " does not exist")
(lookup tn nodeTypes)
-- Temporary types to be removed
type Ngrams = (Text, Text, Text)
type Ngrams = (Text, Text, Text)
type ErrorMessage = Text
-- Queries
type ParentId = NodeId
type Limit = Int
type Offset = Int
type Offset = Int
{-|
Module : Gargantext.
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
{-# LANGUAGE NoImplicitPrelude #-}
module Gargantext.Utils.DateUtils where
import Gargantext.Prelude
......
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