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

[PRELUDE] no global implicit any more.

parent b7ef80e7
...@@ -16,7 +16,6 @@ dependencies: ...@@ -16,7 +16,6 @@ dependencies:
library: library:
source-dirs: src source-dirs: src
default-extensions: default-extensions:
- NoImplicitPrelude
ghc-options: ghc-options:
- -Wincomplete-uni-patterns - -Wincomplete-uni-patterns
- -Wincomplete-record-updates - -Wincomplete-record-updates
...@@ -152,7 +151,6 @@ tests: ...@@ -152,7 +151,6 @@ tests:
main: Main.hs main: Main.hs
source-dirs: src-test source-dirs: src-test
default-extensions: default-extensions:
- NoImplicitPrelude
ghc-options: ghc-options:
- -threaded - -threaded
- -rtsopts - -rtsopts
......
...@@ -8,6 +8,8 @@ Stability : experimental ...@@ -8,6 +8,8 @@ Stability : experimental
Portability : POSIX Portability : POSIX
-} -}
{-# LANGUAGE NoImplicitPrelude #-}
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Types.Main (Language(..)) import Gargantext.Types.Main (Language(..))
--import qualified Ngrams.Lang.Fr as Fr --import qualified Ngrams.Lang.Fr as Fr
......
{-|
Module : Ngrams.Lang
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
Here is a longer description of this module, containing some
commentary with @some markup@.
-}
{-# LANGUAGE NoImplicitPrelude #-}
module Ngrams.Lang where module Ngrams.Lang where
import Gargantext.Prelude (IO()) import Gargantext.Prelude (IO())
......
{-|
Module : Ngrams.Lang
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
Here is a longer description of this module, containing some
commentary with @some markup@.
-}
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE NoImplicitPrelude #-}
...@@ -21,7 +34,7 @@ ngramsExtractionTest = hspec $ do ...@@ -21,7 +34,7 @@ ngramsExtractionTest = hspec $ do
it "\"Of\" seperates two ngrams" $ do it "\"Of\" seperates two ngrams" $ do
t1 <- map (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")]] t1 `shouldBe` [[("Alcoholic extract of Kaempferia galanga","NN","LOCATION"),("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 it "Tests the conjunction of coordination in two ngrams with its adjectives" $ do
t2 <- map (selectNgrams EN) <$> extractNgrams EN (textTest !! 2) t2 <- map (selectNgrams EN) <$> extractNgrams EN (textTest !! 2)
......
{-|
Module : Ngrams.Lang
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
Here is a longer description of this module, containing some
commentary with @some markup@.
-}
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE NoImplicitPrelude #-}
...@@ -32,7 +45,7 @@ ngramsExtractionTest = hspec $ do ...@@ -32,7 +45,7 @@ ngramsExtractionTest = hspec $ do
it "Groupe : nom commun et adjectifs avec conjonction" $ do it "Groupe : nom commun et adjectifs avec conjonction" $ do
let textFr = "Le livre blanc et rouge." let textFr = "Le livre blanc et rouge."
testFr <- map (selectNgrams FR) <$> (extractNgrams FR) textFr testFr <- map (selectNgrams FR) <$> (extractNgrams FR) textFr
testFr `shouldBe` [[("livre blanc","N","O"),("livre rouge","N","O")]] testFr `shouldBe` [[("livre blanc","NC","O"),("livre rouge","NC","O")]]
-- `shouldBe` [[("livre blanc et rouge","N","O")]] ? -- `shouldBe` [[("livre blanc et rouge","N","O")]] ?
it "Groupe: Nom commun + préposition + Nom commun" $ do it "Groupe: Nom commun + préposition + Nom commun" $ do
......
{-|
Module : Ngrams.Lang.Occurrences
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
Here is a longer description of this module, containing some
commentary with @some markup@.
-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ScopedTypeVariables #-}
......
{-|
Module : Ngrams.Metrics
Description :
Copyright : Ngrams.Metrics (c)
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
Here is a longer description of this module, containing some
commentary with @some markup@.
-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# LANGUAGE CPP #-} {-# LANGUAGE CPP #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Ngrams.Metrics (main) where module Ngrams.Metrics (main) where
......
{-|
Module : Parsers.Date
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
Here is a longer description of this module, containing some
commentary with @some markup@.
-}
{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE NoImplicitPrelude #-}
module Parsers.Date where module Parsers.Date where
......
{-|
Module : Parsers.Types
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
Here is a longer description of this module, containing some
commentary with @some markup@.
-}
{-# OPTIONS_GHC -fno-warn-orphans #-} {-# OPTIONS_GHC -fno-warn-orphans #-}
{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE StandaloneDeriving #-}
......
{-|
Module : WOS
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
Here is a longer description of this module, containing some
commentary with @some markup@.
-}
{-# LANGUAGE NoImplicitPrelude #-}
module Parsers.WOS where module Parsers.WOS where
{-|
Module : Gargantext
Description : Textmining platform
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
@Gargantext@: search, map, share
-}
module Gargantext ( module Gargantext (
module Gargantext.Database, module Gargantext.Database,
-- module Gargantext.Ngrams, -- module Gargantext.Ngrams,
......
...@@ -20,15 +20,17 @@ Thanks @yannEsposito for this. ...@@ -20,15 +20,17 @@ Thanks @yannEsposito for this.
{-# OPTIONS_GHC -fno-warn-name-shadowing #-} {-# OPTIONS_GHC -fno-warn-name-shadowing #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE DataKinds #-}
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE KindSignatures #-} {-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE KindSignatures #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
--------------------------------------------------------------------- ---------------------------------------------------------------------
module Gargantext.API module Gargantext.API
......
...@@ -19,8 +19,10 @@ Main authorisation of Gargantext are managed in this module ...@@ -19,8 +19,10 @@ Main authorisation of Gargantext are managed in this module
-} -}
{-# OPTIONS_GHC -fno-warn-name-shadowing #-} {-# OPTIONS_GHC -fno-warn-name-shadowing #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TemplateHaskell #-}
module Gargantext.API.Auth module Gargantext.API.Auth
where where
......
...@@ -11,12 +11,15 @@ Count API part of Gargantext. ...@@ -11,12 +11,15 @@ Count API part of Gargantext.
-} -}
{-# OPTIONS_GHC -fno-warn-name-shadowing #-} {-# OPTIONS_GHC -fno-warn-name-shadowing #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-} {-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TypeOperators #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE OverloadedStrings #-}
module Gargantext.API.Count module Gargantext.API.Count
where where
......
...@@ -10,8 +10,10 @@ Portability : POSIX ...@@ -10,8 +10,10 @@ Portability : POSIX
{-# OPTIONS_GHC -fno-warn-name-shadowing #-} {-# OPTIONS_GHC -fno-warn-name-shadowing #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TemplateHaskell #-}
--------------------------------------------------------------------- ---------------------------------------------------------------------
module Gargantext.API.FrontEnd module Gargantext.API.FrontEnd
......
...@@ -11,10 +11,12 @@ Node API ...@@ -11,10 +11,12 @@ Node API
-} -}
{-# OPTIONS_GHC -fno-warn-name-shadowing #-} {-# OPTIONS_GHC -fno-warn-name-shadowing #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE DataKinds #-}
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE OverloadedStrings #-}
------------------------------------------------------------------- -------------------------------------------------------------------
module Gargantext.API.Node module Gargantext.API.Node
......
{-| {-|PI/Application.hs
API/Count.hs
API/FrontEnd.hs
API/Node.hs
API/Auth.hs
API.hs
Database/NodeNodeNgram.hs
Database/User.hs
Database/Queries.hs
Module : Gargantext.API.Settings Module : Gargantext.API.Settings
Description : Settings of the API (Server and Client) Description : Settings of the API (Server and Client)
Copyright : (c) CNRS, 2017-Present Copyright : (c) CNRS, 2017-Present
...@@ -11,6 +20,7 @@ Portability : POSIX ...@@ -11,6 +20,7 @@ Portability : POSIX
{-# OPTIONS_GHC -fno-warn-name-shadowing #-} {-# OPTIONS_GHC -fno-warn-name-shadowing #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE DataKinds #-} {-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ScopedTypeVariables #-}
......
{-|
Module : Gargantext.Database
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
Here is a longer description of this module, containing some
commentary with @some markup@.
-}
{-# LANGUAGE NoImplicitPrelude #-}
module Gargantext.Database ( module Gargantext.Database (
module Gargantext.Database.Utils module Gargantext.Database.Utils
-- , module Gargantext.Database.Instances -- , module Gargantext.Database.Instances
......
...@@ -11,14 +11,15 @@ Portability : POSIX ...@@ -11,14 +11,15 @@ Portability : POSIX
{-# OPTIONS_GHC -fno-warn-orphans #-} {-# OPTIONS_GHC -fno-warn-orphans #-}
{-# OPTIONS_GHC -fno-warn-name-shadowing #-} {-# OPTIONS_GHC -fno-warn-name-shadowing #-}
{-# LANGUAGE Arrows #-} {-# LANGUAGE Arrows #-}
{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE NoMonomorphismRestriction #-} {-# LANGUAGE NoMonomorphismRestriction #-}
{-# LANGUAGE TemplateHaskell #-}
------------------------------------------------------------------------ ------------------------------------------------------------------------
module Gargantext.Database.Facet module Gargantext.Database.Facet
......
{-# LANGUAGE FlexibleInstances #-} {-|
{-# LANGUAGE MultiParamTypeClasses #-} Module : Gargantext.Database.Instances
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
Here is a longer description of this module, containing some
commentary with @some markup@.
-}
{-# OPTIONS_GHC -fno-warn-orphans #-} {-# OPTIONS_GHC -fno-warn-orphans #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NoImplicitPrelude #-}
module Gargantext.Database.Instances where module Gargantext.Database.Instances where
import Gargantext.Prelude import Gargantext.Prelude
......
{-# LANGUAGE TemplateHaskell #-} {-|
{-# LANGUAGE FlexibleInstances #-} Module : Gargantext.Databse.Ngram
{-# LANGUAGE MultiParamTypeClasses #-} Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
Here is a longer description of this module, containing some
commentary with @some markup@.
-}
{-# LANGUAGE Arrows #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE Arrows #-} {-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE TemplateHaskell #-}
module Gargantext.Database.Ngram where module Gargantext.Database.Ngram where
......
...@@ -9,13 +9,15 @@ Portability : POSIX ...@@ -9,13 +9,15 @@ Portability : POSIX
-} -}
{-# OPTIONS_GHC -fno-warn-name-shadowing #-} {-# OPTIONS_GHC -fno-warn-name-shadowing #-}
{-# LANGUAGE TemplateHaskell #-} {-# OPTIONS_GHC -fno-warn-orphans #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE Arrows #-}
{-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE Arrows #-} {-# LANGUAGE MultiParamTypeClasses #-}
{-# OPTIONS_GHC -fno-warn-orphans #-} {-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE TemplateHaskell #-}
module Gargantext.Database.Node where module Gargantext.Database.Node where
......
{-# LANGUAGE TemplateHaskell #-} {-|
{-# LANGUAGE FlexibleInstances #-} Module : Gargantext.Database.NodeNgram
{-# LANGUAGE MultiParamTypeClasses #-} Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
Here is a longer description of this module, containing some
commentary with @some markup@.
-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# LANGUAGE Arrows #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE Arrows #-} {-# LANGUAGE MultiParamTypeClasses #-}
{-# OPTIONS_GHC -fno-warn-orphans #-} {-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE TemplateHaskell #-}
module Gargantext.Database.NodeNgram where module Gargantext.Database.NodeNgram where
......
{-# LANGUAGE TemplateHaskell #-} {-|
{-# LANGUAGE FlexibleInstances #-} Module : Gargantext.Database.NodeNgramNgram
{-# LANGUAGE MultiParamTypeClasses #-} Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
Here is a longer description of this module, containing some
commentary with @some markup@.
-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# LANGUAGE Arrows #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE Arrows #-} {-# LANGUAGE MultiParamTypeClasses #-}
{-# OPTIONS_GHC -fno-warn-orphans #-} {-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE TemplateHaskell #-}
module Gargantext.Database.NodeNgramNgram where module Gargantext.Database.NodeNgramNgram where
......
{-# LANGUAGE TemplateHaskell #-} {-|
{-# LANGUAGE FlexibleInstances #-} Module : Gargantext.Database.NodeNode
{-# LANGUAGE MultiParamTypeClasses #-} Description :
{-# LANGUAGE FunctionalDependencies #-} Copyright : (c) CNRS, 2017-Present
{-# LANGUAGE Arrows #-} License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
Here is a longer description of this module, containing some
commentary with @some markup@.
-}
{-# OPTIONS_GHC -fno-warn-orphans #-} {-# OPTIONS_GHC -fno-warn-orphans #-}
{-# LANGUAGE Arrows #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE TemplateHaskell #-}
module Gargantext.Database.NodeNode where module Gargantext.Database.NodeNode where
import Prelude import Prelude
......
{-|
Module : Gargantext.Database.NodeNodeNgram
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
Here is a longer description of this module, containing some
commentary with @some markup@.
-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE MultiParamTypeClasses #-}
......
...@@ -9,13 +9,15 @@ Portability : POSIX ...@@ -9,13 +9,15 @@ Portability : POSIX
-} -}
{-# OPTIONS_GHC -fno-warn-name-shadowing #-} {-# OPTIONS_GHC -fno-warn-name-shadowing #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE Arrows #-}
{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE Arrows #-} {-# LANGUAGE MultiParamTypeClasses #-}
{-# OPTIONS_GHC -fno-warn-orphans #-} {-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Gargantext.Database.Queries where module Gargantext.Database.Queries where
......
{-|
Module : Gargantext.Database.user
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
Here is a longer description of this module, containing some
commentary with @some markup@.
-}
{-# OPTIONS_GHC -fno-warn-name-shadowing #-} {-# OPTIONS_GHC -fno-warn-name-shadowing #-}
{-# OPTIONS_GHC -fno-warn-orphans #-} {-# OPTIONS_GHC -fno-warn-orphans #-}
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE MultiParamTypeClasses #-}
......
{-|
Module : Gargantext.Database.Util
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
Here is a longer description of this module, containing some
commentary with @some markup@.
-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE FlexibleContexts #-}
module Gargantext.Database.Utils where module Gargantext.Database.Utils where
......
...@@ -14,6 +14,8 @@ n non negative integer ...@@ -14,6 +14,8 @@ n non negative integer
-} -}
{-# LANGUAGE NoImplicitPrelude #-}
module Gargantext.Ngrams ( module Gargantext.Ngrams.Letters module Gargantext.Ngrams ( module Gargantext.Ngrams.Letters
--, module Gargantext.Ngrams.Hetero --, module Gargantext.Ngrams.Hetero
, module Gargantext.Ngrams.CoreNLP , module Gargantext.Ngrams.CoreNLP
......
...@@ -11,6 +11,8 @@ Domain Specific Language to manage Frequent Item Set (FIS) ...@@ -11,6 +11,8 @@ Domain Specific Language to manage Frequent Item Set (FIS)
-} -}
{-# LANGUAGE NoImplicitPrelude #-}
module Gargantext.Ngrams.FrequentItemSet module Gargantext.Ngrams.FrequentItemSet
( Fis, Size ( Fis, Size
, occ, cooc , occ, cooc
......
{-# LANGUAGE OverloadedStrings #-} {-|
Module : Gargantext.Ngrams.Lang.En
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
Here is a longer description of this module, containing some
commentary with @some markup@.
-}
{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module Gargantext.Ngrams.Lang.En (selectNgrams, groupNgrams, textTest) where module Gargantext.Ngrams.Lang.En (selectNgrams, groupNgrams, textTest) where
......
{-# LANGUAGE OverloadedStrings #-} {-|
Module : Gargantext.Ngrams.Lang.Fr
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
Here is a longer description of this module, containing some
commentary with @some markup@.
-}
{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module Gargantext.Ngrams.Lang.Fr (selectNgrams, groupNgrams, textTest) module Gargantext.Ngrams.Lang.Fr (selectNgrams, groupNgrams, textTest)
where where
......
...@@ -11,6 +11,7 @@ Sugar to work on letters with Text. ...@@ -11,6 +11,7 @@ Sugar to work on letters with Text.
-} -}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
module Gargantext.Ngrams.Letters where module Gargantext.Ngrams.Letters where
......
{-|
Module : Gargantext.Ngrams.List
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
Here is a longer description of this module, containing some
commentary with @some markup@.
-}
{-# LANGUAGE NoImplicitPrelude #-}
module Gargantext.Ngrams.List where module Gargantext.Ngrams.List where
import Data.Maybe import Data.Maybe
......
...@@ -11,6 +11,8 @@ Portability : POSIX ...@@ -11,6 +11,8 @@ Portability : POSIX
Mainly reexport functions in @Data.Text.Metrics@ Mainly reexport functions in @Data.Text.Metrics@
-} -}
{-# LANGUAGE NoImplicitPrelude #-}
module Gargantext.Ngrams.Metrics (levenshtein module Gargantext.Ngrams.Metrics (levenshtein
, levenshteinNorm , levenshteinNorm
, damerauLevenshtein , damerauLevenshtein
......
{-|
Module : Gargantext.Ngrams.Occurrences
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
Here is a longer description of this module, containing some
commentary with @some markup@.
-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
module Gargantext.Ngrams.Occurrences where module Gargantext.Ngrams.Occurrences where
......
{-# LANGUAGE OverloadedStrings #-} {-|
{-# LANGUAGE ScopedTypeVariables #-} Module : Gargantext.Ngrams.Parser
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
Here is a longer description of this module, containing some
commentary with @some markup@.
-}
{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Gargantext.Ngrams.Parser where module Gargantext.Ngrams.Parser where
......
...@@ -11,7 +11,9 @@ Definition of TFICF ...@@ -11,7 +11,9 @@ Definition of TFICF
-} -}
{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE NoImplicitPrelude #-}
module Gargantext.Ngrams.TFICF where module Gargantext.Ngrams.TFICF where
......
{-|
Module : Gargantext.Ngrams.TextMining
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
Here is a longer description of this module, containing some
commentary with @some markup@.
-}
{-# LANGUAGE NoImplicitPrelude #-}
module Gargantext.Ngrams.TextMining where module Gargantext.Ngrams.TextMining where
......
...@@ -18,6 +18,8 @@ This module mainly describe how to add a new parser to Gargantext, ...@@ -18,6 +18,8 @@ This module mainly describe how to add a new parser to Gargantext,
please follow the types. please follow the types.
-} -}
{-# LANGUAGE NoImplicitPrelude #-}
module Gargantext.Parsers -- (parse, FileFormat(..)) module Gargantext.Parsers -- (parse, FileFormat(..))
where where
......
...@@ -14,9 +14,9 @@ import Gargantext.Parsers.Date as DGP ...@@ -14,9 +14,9 @@ import Gargantext.Parsers.Date as DGP
DGP.parseDate1 DGP.FR "12 avril 2010" == "2010-04-12T00:00:00.000+00:00" DGP.parseDate1 DGP.FR "12 avril 2010" == "2010-04-12T00:00:00.000+00:00"
-} -}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module Gargantext.Parsers.Date (parseDate1, Lang(FR, EN), parseDate, fromRFC3339, parseTimeOfDay, getMultiplicator) where module Gargantext.Parsers.Date (parseDate1, Lang(FR, EN), parseDate, fromRFC3339, parseTimeOfDay, getMultiplicator) where
......
{-|
Module : Gargantext.Parsers.WOS
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
Here is a longer description of this module, containing some
commentary with @some markup@.
-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
module Gargantext.Parsers.WOS (wosParser) where module Gargantext.Parsers.WOS (wosParser) where
......
{-|
Module : Gargantext.Prelude
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
Here is a longer description of this module, containing some
commentary with @some markup@.
-}
{-# OPTIONS_GHC -fno-warn-name-shadowing #-} {-# OPTIONS_GHC -fno-warn-name-shadowing #-}
{-# OPTIONS_GHC -fno-warn-type-defaults #-} {-# OPTIONS_GHC -fno-warn-type-defaults #-}
{-# LANGUAGE NoImplicitPrelude #-}
{- {-# LANGUAGE NoImplicitPrelude #-}
TODO: import head impossible from Protolude: why ?
-}
module Gargantext.Prelude module Gargantext.Prelude
( module Gargantext.Prelude ( module Gargantext.Prelude
......
{-|
Module : Gargantext.Types
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
Here is a longer description of this module, containing some
commentary with @some markup@.
-}
{-# LANGUAGE NoImplicitPrelude #-}
module Gargantext.Types ( module Gargantext.Types.Main module Gargantext.Types ( module Gargantext.Types.Main
, module Gargantext.Types.Node , module Gargantext.Types.Node
) where ) where
......
...@@ -13,9 +13,10 @@ commentary with @some markup@. ...@@ -13,9 +13,10 @@ commentary with @some markup@.
{-# OPTIONS_GHC -fno-warn-name-shadowing #-} {-# OPTIONS_GHC -fno-warn-name-shadowing #-}
{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
------------------------------------------------------------------------ ------------------------------------------------------------------------
module Gargantext.Types.Main where module Gargantext.Types.Main where
......
...@@ -10,10 +10,12 @@ Portability : POSIX ...@@ -10,10 +10,12 @@ Portability : POSIX
-} -}
{-# OPTIONS_GHC -fno-warn-orphans #-} {-# OPTIONS_GHC -fno-warn-orphans #-}
{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
-- {-# LANGUAGE DuplicateRecordFields #-} -- {-# LANGUAGE DuplicateRecordFields #-}
module Gargantext.Types.Node where module Gargantext.Types.Node where
......
...@@ -18,8 +18,9 @@ the number of chars). ...@@ -18,8 +18,9 @@ the number of chars).
Phylomemy was first described in [REF]. Phylomemy was first described in [REF].
-} -}
{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE TemplateHaskell #-}
module Gargantext.Types.Phylo where module Gargantext.Types.Phylo where
......
{-|
Module : Gargantext.Utils
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
Here is a longer description of this module, containing some
commentary with @some markup@.
-}
{-# LANGUAGE NoImplicitPrelude #-}
module Gargantext.Utils ( module Gargantext.Utils (
-- module Gargantext.Utils.Chronos -- module Gargantext.Utils.Chronos
module Gargantext.Utils.Prefix module Gargantext.Utils.Prefix
......
{-|
Module : Gargantext.Utils.Counts
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
Here is a longer description of this module, containing some
commentary with @some markup@.
-}
{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE BangPatterns #-} {-# LANGUAGE BangPatterns #-}
......
{-| {-|
Module : Gargantext. Module : Gargantext.Utils.DateUtils
Description : Description :
Copyright : (c) CNRS, 2017-Present Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
......
{-|
Module : Gargantext.Utils.Prefix
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
Here is a longer description of this module, containing some
commentary with @some markup@.
-}
{-# LANGUAGE NoImplicitPrelude #-}
module Gargantext.Utils.Prefix where module Gargantext.Utils.Prefix where
......
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