Commit 596c940d authored by Alexandre Delanoë's avatar Alexandre Delanoë

[UPGRADE] LTS 12.10.

parent a3490841
......@@ -99,9 +99,10 @@ library:
- hlcm
- ini
- jose-jwt
- kmeans-vector
# - kmeans-vector
- KMP
- lens
- located-base
- logging-effect
- matrix
- monad-logger
......@@ -112,7 +113,6 @@ library:
- path
- path-io
- postgresql-simple
- pretty
- probability
- product-profunctors
- profunctors
......
......@@ -11,7 +11,7 @@ Count API part of Gargantext.
-}
{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
{-# OPTIONS_GHC -fno-warn-warnings-deprecations #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE DataKinds #-}
......
......@@ -24,6 +24,7 @@ module Gargantext.Core.Types ( module Gargantext.Core.Types.Main
import GHC.Generics
import Data.Aeson
import Data.Semigroup
import Data.Monoid
import Data.Set (Set, empty)
--import qualified Data.Set as S
......@@ -103,16 +104,19 @@ data TokenTag = TokenTag { _my_token_word :: [Text]
, _my_token_ner :: Maybe NER
} deriving (Show)
instance Semigroup TokenTag where
(<>) (TokenTag w1 s1 p1 n1) (TokenTag w2 s2 p2 _) = TokenTag (w1 <> w2) (s1 <> s2) p3 n1
where
p3 = case (p1,p2) of
(Just JJ, Just NP) -> Just NP
(Just VB, Just NP) -> Just NP
_ -> p1
instance Monoid TokenTag where
mempty = TokenTag [] empty Nothing Nothing
mappend (TokenTag w1 s1 p1 n1) (TokenTag w2 s2 p2 _)
= TokenTag (w1 <> w2) (s1 <> s2) p3 n1
where
p3 = case (p1,p2) of
(Just JJ, Just NP) -> Just NP
(Just VB, Just NP) -> Just NP
_ -> p1
mappend t1 t2 = (<>) t1 t2
mconcat = foldl mappend mempty
......@@ -20,6 +20,7 @@ module Gargantext.Prelude
( module Gargantext.Prelude
, module Protolude
, headMay, lastMay
, module GHC.Err.Located
, module Text.Show
, module Text.Read
, cs
......@@ -29,7 +30,7 @@ module Gargantext.Prelude
where
import GHC.Exts (sortWith)
import GHC.Err.Located (undefined)
import Control.Monad.IO.Class (MonadIO)
import Data.Maybe (isJust, fromJust, maybe)
import Protolude ( Bool(True, False), Int, Int64, Double, Integer
......@@ -42,7 +43,7 @@ import Protolude ( Bool(True, False), Int, Int64, Double, Integer
, Ord, Integral, Foldable, RealFrac, Monad, filter
, reverse, map, mapM, zip, drop, take, zipWith
, sum, fromIntegral, length, fmap, foldl, foldl'
, takeWhile, sqrt, undefined, identity
, takeWhile, sqrt, identity
, abs, min, max, maximum, minimum, return, snd, truncate
, (+), (*), (/), (-), (.), ($), (&), (**), (^), (<), (>), log
, Eq, (==), (>=), (<=), (<>), (/=)
......@@ -51,7 +52,6 @@ import Protolude ( Bool(True, False), Int, Int64, Double, Integer
, elem, die, mod, div, const, either
, curry, uncurry, repeat
, otherwise, when
, undefined
, IO()
, compare
, on
......@@ -137,8 +137,8 @@ chunkAlong' a b l = only (while dropAlong)
dropAlong = V.scanl (\x _y -> V.drop b x) l (V.fromList [1..])
-- | TODO Inverse of chunk ? unchunkAlong ?
unchunkAlong :: Int -> Int -> [[a]] -> [a]
unchunkAlong = undefined
-- unchunkAlong :: Int -> Int -> [[a]] -> [a]
-- unchunkAlong = undefined
-- splitAlong [2,3,4] ("helloworld" :: [Char]) == ["he", "llo", "worl", "d"]
......
......@@ -46,8 +46,8 @@ import Gargantext.Text.Terms.Mono (monoTerms)
data TermType lang = Mono lang | Multi lang | MonoMulti lang
group :: [Text] -> [Text]
group = undefined
--group :: [Text] -> [Text]
--group = undefined
-- remove Stop Words
-- map (filter (\t -> not . elem t)) $
......
resolver: lts-12.10
flags: {}
extra-package-dbs: []
packages:
......@@ -17,30 +18,27 @@ extra-deps:
- accelerate-1.2.0.0
- hashtables-1.2.3.0 # needed by accelerate-1.2.0.0
- aeson-1.2.4.0
- opaleye-0.6.7002.0
- aeson-lens-0.5.0.0
- duckling-0.1.3.0
- extra-1.5.3
- full-text-search-0.2.1.4
- fullstop-0.1.4
- haskell-src-exts-1.18.2
- http-types-0.12.1
- kmeans-vector-0.3.2
# - kmeans-vector-0.3.2
- probable-0.1.3
- protolude-0.2
- rake-0.0.1
- servant-0.13
- servant-auth-0.3.0.1
- servant-client-0.13
- located-base-0.1.1.1
- servant-client-core-0.13
- servant-docs-0.11.1
- servant-multipart-0.11.1
- servant-server-0.13
- servant-swagger-ui-0.2.3.2.2.8
- stemmer-0.5.2
# - text-1.2.3.0
- text-show-3.6.2
- servant-flatten-0.2
- serialise-0.2.0.0 # imt-api-client
- cborg-0.2.0.0 # imt-api-client
- KMP-0.1.0.2
resolver: lts-11.10
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