Commit 67e1e32d authored by Alexandre Delanoë's avatar Alexandre Delanoë

[STACK LTS] upgrade + external API deps.

parent f8b3f9de
Pipeline #546 failed with stage
...@@ -30,7 +30,7 @@ library: ...@@ -30,7 +30,7 @@ library:
- Gargantext.API.FrontEnd - Gargantext.API.FrontEnd
- Gargantext.API.Ngrams - Gargantext.API.Ngrams
- Gargantext.API.Node - Gargantext.API.Node
- Gargantext.API.Orchestrator # - Gargantext.API.Orchestrator
- Gargantext.API.Search - Gargantext.API.Search
- Gargantext.API.Settings - Gargantext.API.Settings
- Gargantext.Core - Gargantext.Core
...@@ -168,7 +168,7 @@ library: ...@@ -168,7 +168,7 @@ library:
- servant-auth - servant-auth
- servant-blaze - servant-blaze
- servant-client - servant-client
- servant-job # - servant-job
- servant-mock - servant-mock
- servant-multipart - servant-multipart
- servant-server - servant-server
......
...@@ -126,7 +126,7 @@ instance HasInvalidError GargError where ...@@ -126,7 +126,7 @@ instance HasInvalidError GargError where
instance HasTreeError GargError where instance HasTreeError GargError where
_TreeError = _GargTreeError _TreeError = _GargTreeError
showAsServantErr :: Show a => a -> ServantErr showAsServantErr :: Show a => a -> ServerError
showAsServantErr a = err500 { errBody = BL8.pack $ show a } showAsServantErr a = err500 { errBody = BL8.pack $ show a }
fireWall :: Applicative f => Request -> FireWall -> f Bool fireWall :: Applicative f => Request -> FireWall -> f Bool
......
...@@ -56,7 +56,7 @@ import Data.Map.Strict (Map) ...@@ -56,7 +56,7 @@ import Data.Map.Strict (Map)
import qualified Data.Set as Set import qualified Data.Set as Set
import Control.Category ((>>>)) import Control.Category ((>>>))
import Control.Concurrent import Control.Concurrent
import Control.Lens (makeLenses, makePrisms, Getter, Iso', iso, from, (.~), (?=), (#), to, folded, {-withIndex, ifolded,-} view, use, (^.), (^..), (^?), (+~), (%~), (%=), sumOf, at, _Just, Each(..), itraverse_, both, forOf_, (%%~)) import Control.Lens (makeLenses, makePrisms, Getter, Iso', iso, from, (.~), (?=), (#), to, folded, {-withIndex, ifolded,-} view, use, (^.), (^..), (^?), (+~), (%~), (%=), sumOf, at, _Just, Each(..), itraverse_, both, forOf_, (%%~), (?~))
import Control.Monad.Error.Class (MonadError) import Control.Monad.Error.Class (MonadError)
import Control.Monad.Reader import Control.Monad.Reader
import Control.Monad.State import Control.Monad.State
...@@ -441,11 +441,11 @@ instance (Eq a, Arbitrary a) => Arbitrary (Replace a) where ...@@ -441,11 +441,11 @@ instance (Eq a, Arbitrary a) => Arbitrary (Replace a) where
-- If they happen to be equal then the patch is Keep. -- If they happen to be equal then the patch is Keep.
instance ToSchema a => ToSchema (Replace a) where instance ToSchema a => ToSchema (Replace a) where
declareNamedSchema (_ :: proxy (Replace a)) = do declareNamedSchema (_ :: Proxy (Replace a)) = do
-- TODO Keep constructor is not supported here. -- TODO Keep constructor is not supported here.
aSchema <- declareSchemaRef (Proxy :: Proxy a) aSchema <- declareSchemaRef (Proxy :: Proxy a)
return $ NamedSchema (Just "Replace") $ mempty return $ NamedSchema (Just "Replace") $ mempty
& type_ .~ SwaggerObject & type_ ?~ SwaggerObject
& properties .~ & properties .~
InsOrdHashMap.fromList InsOrdHashMap.fromList
[ ("old", aSchema) [ ("old", aSchema)
......
...@@ -46,7 +46,7 @@ import qualified Data.ByteString.Lazy as L ...@@ -46,7 +46,7 @@ import qualified Data.ByteString.Lazy as L
import Servant import Servant
import Servant.Client (BaseUrl, parseBaseUrl) import Servant.Client (BaseUrl, parseBaseUrl)
import Servant.Job.Async (newJobEnv, defaultSettings) --import Servant.Job.Async (newJobEnv, defaultSettings)
import Web.HttpApiData (parseUrlPiece) import Web.HttpApiData (parseUrlPiece)
import qualified Jose.Jwk as Jose import qualified Jose.Jwk as Jose
import qualified Jose.Jwa as Jose import qualified Jose.Jwa as Jose
...@@ -60,7 +60,7 @@ import Control.Lens ...@@ -60,7 +60,7 @@ import Control.Lens
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Database.Utils (databaseParameters, HasConnection(..), Cmd', runCmd) import Gargantext.Database.Utils (databaseParameters, HasConnection(..), Cmd', runCmd)
import Gargantext.API.Ngrams (NgramsRepo, HasRepoVar(..), HasRepoSaver(..), HasRepo(..), RepoEnv(..), r_version, saveRepo, initRepo, renv_var, renv_lock) import Gargantext.API.Ngrams (NgramsRepo, HasRepoVar(..), HasRepoSaver(..), HasRepo(..), RepoEnv(..), r_version, saveRepo, initRepo, renv_var, renv_lock)
import Gargantext.API.Orchestrator.Types --import Gargantext.API.Orchestrator.Types
type PortNumber = Int type PortNumber = Int
...@@ -147,7 +147,7 @@ data Env = Env ...@@ -147,7 +147,7 @@ data Env = Env
, _env_repo :: !RepoEnv , _env_repo :: !RepoEnv
, _env_manager :: !Manager , _env_manager :: !Manager
, _env_self_url :: !BaseUrl , _env_self_url :: !BaseUrl
, _env_scrapers :: !ScrapersEnv --, _env_scrapers :: !ScrapersEnv
} }
deriving (Generic) deriving (Generic)
...@@ -243,7 +243,7 @@ newEnv port file = do ...@@ -243,7 +243,7 @@ newEnv port file = do
param <- databaseParameters file param <- databaseParameters file
conn <- connect param conn <- connect param
repo <- readRepoEnv repo <- readRepoEnv
scrapers_env <- newJobEnv defaultSettings manager --scrapers_env <- newJobEnv defaultSettings manager
logger <- newStderrLoggerSet defaultBufSize logger <- newStderrLoggerSet defaultBufSize
pure $ Env pure $ Env
...@@ -252,7 +252,7 @@ newEnv port file = do ...@@ -252,7 +252,7 @@ newEnv port file = do
, _env_conn = conn , _env_conn = conn
, _env_repo = repo , _env_repo = repo
, _env_manager = manager , _env_manager = manager
, _env_scrapers = scrapers_env --, _env_scrapers = scrapers_env
, _env_self_url = self_url , _env_self_url = self_url
} }
...@@ -305,7 +305,7 @@ withDevEnv iniPath k = do ...@@ -305,7 +305,7 @@ withDevEnv iniPath k = do
runCmdRepl :: Show err => Cmd' DevEnv err a -> IO a runCmdRepl :: Show err => Cmd' DevEnv err a -> IO a
runCmdRepl f = withDevEnv "gargantext.ini" $ \env -> runCmdDev env f runCmdRepl f = withDevEnv "gargantext.ini" $ \env -> runCmdDev env f
runCmdReplServantErr :: Cmd' DevEnv ServantErr a -> IO a runCmdReplServantErr :: Cmd' DevEnv ServerError a -> IO a
runCmdReplServantErr = runCmdRepl runCmdReplServantErr = runCmdRepl
-- Use only for dev -- Use only for dev
...@@ -324,5 +324,5 @@ runCmdDevNoErr :: DevEnv -> Cmd' DevEnv () a -> IO a ...@@ -324,5 +324,5 @@ runCmdDevNoErr :: DevEnv -> Cmd' DevEnv () a -> IO a
runCmdDevNoErr = runCmdDev runCmdDevNoErr = runCmdDev
-- Use only for dev -- Use only for dev
runCmdDevServantErr :: DevEnv -> Cmd' DevEnv ServantErr a -> IO a runCmdDevServantErr :: DevEnv -> Cmd' DevEnv ServerError a -> IO a
runCmdDevServantErr = runCmdDev runCmdDevServantErr = runCmdDev
{-|
Module : Gargantext.API.Utils
Description : Server API main Types
Copyright : (c) CNRS, 2017-Present
License : BSD3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
Mainly copied from Servant.Job.Utils (Thanks)
-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE NoImplicitPrelude #-}
module Gargantext.API.Utils
where
import Gargantext.Prelude
import Data.Maybe (Maybe, fromMaybe)
import Prelude (String)
import qualified Data.Text as T
import Data.Swagger
import Data.Text (Text)
swaggerOptions :: Text -> SchemaOptions
swaggerOptions pref = defaultSchemaOptions
{ Data.Swagger.fieldLabelModifier = modifier pref
, Data.Swagger.unwrapUnaryRecords = False
}
modifier :: Text -> String -> String
modifier pref field = T.unpack
$ T.stripPrefix pref (T.pack field) ?! "Expecting prefix " <> T.unpack pref
infixr 4 ?|
-- Reverse infix form of "fromMaybe"
(?|) :: Maybe a -> a -> a
(?|) = flip fromMaybe
infixr 4 ?!
-- Reverse infix form of "fromJust" with a custom error message
(?!) :: Maybe a -> String -> a
(?!) ma' msg = ma' ?| panic (T.pack msg)
...@@ -55,7 +55,7 @@ type Query = Text ...@@ -55,7 +55,7 @@ type Query = Text
type Limit = PubMed.Limit type Limit = PubMed.Limit
get :: ExternalAPIs -> Query -> Maybe Limit -> IO [HyperdataDocument] get :: ExternalAPIs -> Query -> Maybe Limit -> IO [HyperdataDocument]
get PubMed q l = either (\e -> panic $ "CRAWL: PubMed" <> e) (map (toDoc EN)) <$> PubMed.crawler q l get PubMed q l = either (\e -> panic $ "CRAWL: PubMed" <> e) (map (toDoc EN)) <$> PubMed.getMetadataWith q l
get _ _ _ = undefined get _ _ _ = undefined
toDoc :: Lang -> Doc.PubMed -> HyperdataDocument toDoc :: Lang -> Doc.PubMed -> HyperdataDocument
......
...@@ -106,7 +106,7 @@ treeData cId nt lt = do ...@@ -106,7 +106,7 @@ treeData cId nt lt = do
pure $ toTree lt cs' m pure $ toTree lt cs' m
treeData' :: FlowCmdM env ServantErr m treeData' :: FlowCmdM env ServerError m
=> CorpusId -> NgramsType -> ListType => CorpusId -> NgramsType -> ListType
-> m [MyTree] -> m [MyTree]
treeData' cId nt lt = do treeData' cId nt lt = do
......
...@@ -29,6 +29,7 @@ import qualified Data.ByteString as DB ...@@ -29,6 +29,7 @@ import qualified Data.ByteString as DB
import qualified Data.ByteString.Lazy as DBL import qualified Data.ByteString.Lazy as DBL
import Data.Swagger import Data.Swagger
import Gargantext.API.Types import Gargantext.API.Types
import Gargantext.API.Utils (swaggerOptions)
import Gargantext.Database.Types.Node (PhyloId, ListId, CorpusId) import Gargantext.Database.Types.Node (PhyloId, ListId, CorpusId)
import Gargantext.Database.Schema.Node (insertNodes, nodePhyloW, getNodePhylo) import Gargantext.Database.Schema.Node (insertNodes, nodePhyloW, getNodePhylo)
import Gargantext.Database.Types.Node -- (NodePhylo(..)) import Gargantext.Database.Types.Node -- (NodePhylo(..))
...@@ -38,7 +39,6 @@ import Gargantext.Viz.Phylo.Main ...@@ -38,7 +39,6 @@ import Gargantext.Viz.Phylo.Main
import Gargantext.Viz.Phylo.Example import Gargantext.Viz.Phylo.Example
import Gargantext.API.Ngrams (TODO(..)) import Gargantext.API.Ngrams (TODO(..))
import Servant import Servant
import Servant.Job.Utils (swaggerOptions)
import Test.QuickCheck (elements) import Test.QuickCheck (elements)
import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary) import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary)
import Web.HttpApiData (parseUrlPiece, readTextData) import Web.HttpApiData (parseUrlPiece, readTextData)
......
resolver: lts-12.26 resolver: lts-14.1
flags: {} flags: {}
extra-package-dbs: [] extra-package-dbs: []
packages: packages:
...@@ -22,14 +22,21 @@ extra-deps: ...@@ -22,14 +22,21 @@ extra-deps:
commit: 3fe28b683aba5ddf05e3b5f8eced0bd05c5a29f9 commit: 3fe28b683aba5ddf05e3b5f8eced0bd05c5a29f9
- git: https://github.com/robstewart57/rdf4h.git - git: https://github.com/robstewart57/rdf4h.git
commit: 4fd2edf30c141600ffad6d730cc4c1c08a6dbce4 commit: 4fd2edf30c141600ffad6d730cc4c1c08a6dbce4
#
# External API connectin to get data
- git: https://gitlab.iscpif.fr/gargantext/crawlers/pubmed.git - git: https://gitlab.iscpif.fr/gargantext/crawlers/pubmed.git
commit: ac4f8ecfb2e579041a350e4718bc6d4e7a832d92 commit: 01a6bf1e79cd5aef8628b240bbd47cb2a0864d5e
- git: https://gitlab.iscpif.fr/gargantext/crawlers/istex.git
commit: daeae80365250c4bd539f0a65e271f9aa37f731f
- git: https://gitlab.iscpif.fr/gargantext/crawlers/hal.git - git: https://gitlab.iscpif.fr/gargantext/crawlers/hal.git
commit: bf57642f6b66f554fdc0a38ac391cd8200dffcb3 commit: ef9e638c97788df251f50b71fcdd9551b87f12c5
- git: https://gitlab.iscpif.fr/gargantext/crawlers/isidore.git
commit: 3db385e767d2100d8abe900833c6e7de3ac55e1b
#
- git: https://gitlab.iscpif.fr/gargantext/patches-class - git: https://gitlab.iscpif.fr/gargantext/patches-class
commit: 746b4ce0af8f9e600d555ad7e5b2973a940cdad9 commit: 746b4ce0af8f9e600d555ad7e5b2973a940cdad9
- git: https://github.com/np/servant-job.git #- git: https://github.com/np/servant-job.git
commit: ac4227441bbca30c44235582b5ec31340c569021 # commit: ac4227441bbca30c44235582b5ec31340c569021
- git: https://gitlab.iscpif.fr/gargantext/clustering-louvain.git - git: https://gitlab.iscpif.fr/gargantext/clustering-louvain.git
commit: 1c636112b151110408e7c5a28cec39e46657358e commit: 1c636112b151110408e7c5a28cec39e46657358e
- git: https://github.com/np/patches-map - git: https://github.com/np/patches-map
...@@ -38,10 +45,8 @@ extra-deps: ...@@ -38,10 +45,8 @@ extra-deps:
commit: 53385de076be09f728a1b58c035a18e9ff9bcfd6 commit: 53385de076be09f728a1b58c035a18e9ff9bcfd6
- git: https://github.com/delanoe/hsparql.git - git: https://github.com/delanoe/hsparql.git
commit: 308c74b71a1abb0a91546fa57d353131248e3a7f commit: 308c74b71a1abb0a91546fa57d353131248e3a7f
- git: https://gitlab.iscpif.fr/gargantext/crawlers/isidore.git
commit: e39454101b53916e3082085ebfe922df695fc775
- KMP-0.1.0.2 - KMP-0.1.0.2
- accelerate-1.2.0.0 - accelerate-1.2.0.1
- aeson-lens-0.5.0.0 - aeson-lens-0.5.0.0
- deepseq-th-0.1.0.4 - deepseq-th-0.1.0.4
- duckling-0.1.3.0 - duckling-0.1.3.0
...@@ -56,8 +61,9 @@ extra-deps: ...@@ -56,8 +61,9 @@ extra-deps:
- json-stream-0.4.2.4 # Text.Parsers (JSON) - json-stream-0.4.2.4 # Text.Parsers (JSON)
- serialise-0.2.0.0 - serialise-0.2.0.0
- servant-flatten-0.2 - servant-flatten-0.2
- servant-multipart-0.11.2 #- servant-multipart-0.11.2
- stemmer-0.5.2 - stemmer-0.5.2
- time-units-1.0.0 - time-units-1.0.0
- validity-0.9.0.0 # patches-{map,class} - validity-0.9.0.0 # patches-{map,class}
- directory-1.3.1.5 - directory-1.3.1.5
- process-1.6.5.1@sha256:77a9afeb676357f67fe5cf1ad79aca0745fb6f7fb96b786d510af08f622643f6,2468
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