Commit 189813e6 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[External API] list of available APIs through API.

parent 17e8454e
Pipeline #510 failed with stage
......@@ -24,7 +24,7 @@ import qualified Data.Vector as V
import Gargantext.Prelude
import Gargantext.Text.Search
import qualified Gargantext.Text.Parsers.CSV as CSV
import qualified Gargantext.Text.Corpus.Parsers.CSV as CSV
------------------------------------------------------------------------
type Query = [S.Term]
......
......@@ -57,7 +57,7 @@ import Gargantext.Core.Types
import Gargantext.Text.Terms
import Gargantext.Text.Context
import Gargantext.Text.Terms.WithList
import Gargantext.Text.Parsers.CSV (readFile, csv_title, csv_abstract, csv_publication_year)
import Gargantext.Text.Corpus.Parsers.CSV (readFile, csv_title, csv_abstract, csv_publication_year)
import Gargantext.Text.List.CSV (csvGraphTermList)
import Gargantext.Text.Terms (terms)
import Gargantext.Text.Metrics.Count (coocOnContexts, Coocs)
......
......@@ -24,7 +24,7 @@ import Control.Exception (finally)
import Servant (ServantErr)
import Gargantext.Prelude
import Gargantext.Database.Flow (FlowCmdM, flowCorpusFile)
import Gargantext.Text.Parsers (FileFormat(CsvHalFormat))
import Gargantext.Text.Corpus.Parsers (FileFormat(CsvHalFormat))
import Gargantext.Database.Utils (Cmd, )
import Gargantext.Database.Types.Node (CorpusId, toHyperdataDocument)
import Gargantext.Database.Schema.User (insertUsersDemo)
......@@ -33,7 +33,7 @@ import Gargantext.Core (Lang(..))
import Gargantext.API.Node () -- instances
import Gargantext.API.Settings (withDevEnv, runCmdDev, DevEnv)
import System.Environment (getArgs)
--import Gargantext.Text.Parsers.GrandDebat (readFile, GrandDebatReference(..))
--import Gargantext.Text.Corpus.Parsers.GrandDebat (readFile, GrandDebatReference(..))
import qualified Data.Text as Text
import Control.Monad.IO.Class (liftIO)
......
......@@ -31,9 +31,9 @@ import GHC.Generics
import GHC.IO (FilePath)
import Gargantext.Prelude
import Gargantext.Text.List.CSV (csvGraphTermList)
import Gargantext.Text.Parsers.CSV (csv_title, csv_abstract, csv_publication_year)
import qualified Gargantext.Text.Parsers.CSV as CSV
import Gargantext.Text.Parsers (FileFormat(..),parseFile)
import Gargantext.Text.Corpus.Parsers.CSV (csv_title, csv_abstract, csv_publication_year)
import qualified Gargantext.Text.Corpus.Parsers.CSV as CSV
import Gargantext.Text.Corpus.Parsers (FileFormat(..),parseFile)
import Gargantext.Text.Terms.WithList
import Gargantext.Text.Context (TermList)
......
......@@ -47,19 +47,14 @@ library:
- Gargantext.Prelude
- Gargantext.Text
- Gargantext.Text.Context
- Gargantext.Text.Crawlers
- Gargantext.Text.Corpus.Parsers
- Gargantext.Text.Corpus.Parsers.CSV
- Gargantext.Text.Examples
- Gargantext.Text.List.CSV
- Gargantext.Text.Metrics
- Gargantext.Text.Metrics.TFICF
- Gargantext.Text.Metrics.CharByChar
- Gargantext.Text.Metrics.Count
- Gargantext.Text.Parsers
- Gargantext.Text.Parsers.CSV
- Gargantext.Text.Parsers.Date
- Gargantext.Text.Parsers.Wikimedia
- Gargantext.Text.Parsers.WOS
- Gargantext.Text.Parsers.GrandDebat
- Gargantext.Text.Search
- Gargantext.Text.Terms
- Gargantext.Text.Terms.Stop
......
......@@ -318,6 +318,7 @@ serverGargAPI -- orchestrator
:<|> graphAPI -- TODO: mock
:<|> treeAPI
:<|> New.api
:<|> New.info fakeUserId
-- :<|> orchestrator
where
fakeUserId = 1 -- TODO
......
......@@ -38,6 +38,8 @@ import Servant
import Test.QuickCheck (elements)
import Test.QuickCheck.Arbitrary
import Gargantext.Database.Flow (FlowCmdM)
import qualified Gargantext.Text.Corpus.API as API
import Gargantext.Database.Types.Node (UserId)
data Query = Query { query_query :: Text
, query_corpus_id :: Int
......@@ -45,7 +47,7 @@ data Query = Query { query_query :: Text
}
deriving (Eq, Show, Generic)
deriveJSON (unPrefix "query_") ''Query
deriveJSON (unPrefix "query_") 'Query
instance Arbitrary Query where
......@@ -65,9 +67,26 @@ instance ToSchema Query where
type Api = Summary "New Corpus endpoint"
:> ReqBody '[JSON] Query
:> Post '[JSON] CorpusId
:<|> Get '[JSON] ApiInfo
api :: FlowCmdM env err m => Query -> m CorpusId
api (Query q _ _) = do
cId <- flowCorpusSearchInDatabase "user1" EN q
pure cId
------------------------------------------------
data ApiInfo = ApiInfo { api_info :: [API.ExternalAPIs]}
deriving (Generic)
instance Arbitrary ApiInfo where
arbitrary = ApiInfo <$> arbitrary
deriveJSON (unPrefix "") 'ApiInfo
instance ToSchema ApiInfo
info :: FlowCmdM env err m => UserId -> m ApiInfo
info _u = pure $ ApiInfo API.externalAPIs
......@@ -119,6 +119,7 @@ roots = (liftIO (putStrLn ( "/user" :: Text)) >> getNodesWithParentId 0 Nothing)
-- CanPatch (TableNgramsApi)
-- CanFavorite
-- CanMoveToTrash
type NodeAPI a = Get '[JSON] (Node a)
:<|> "rename" :> RenameApi
:<|> PostNodeApi -- TODO move to children POST
......
......@@ -62,8 +62,8 @@ import Gargantext.Ext.IMTUser (deserialiseImtUsersFromFile)
import Gargantext.Prelude
import Gargantext.Text.Terms.Eleve (buildTries, toToken)
import Gargantext.Text.List (buildNgramsLists,StopSize(..))
import Gargantext.Text.Parsers (parseFile, FileFormat)
import qualified Gargantext.Text.Parsers.IsidoreApi as Isidore
import Gargantext.Text.Corpus.Parsers (parseFile, FileFormat)
import qualified Gargantext.Text.Corpus.API.Isidore as Isidore
import Gargantext.Text.Terms (TermType(..), tt_lang, extractTerms, uniText)
import Gargantext.Text.Terms.Mono.Stem.En (stemIt)
import Servant (ServantErr)
......@@ -72,7 +72,7 @@ import qualified Data.List as List
import qualified Data.Map as Map
import qualified Data.Text as Text
import qualified Gargantext.Database.Node.Document.Add as Doc (add)
import qualified Gargantext.Text.Parsers.GrandDebat as GD
import qualified Gargantext.Text.Corpus.Parsers.GrandDebat as GD
type FlowCmdM env err m =
( CmdM env err m
......
......@@ -23,7 +23,7 @@ import qualified Data.Vector as DV
import qualified Data.Map as M
import Gargantext.Text.Metrics.Freq as F
import Gargantext.Text.Parsers.CSV as CSV
import Gargantext.Text.Corpus.Parsers.CSV as CSV
data School = School { school_shortName :: Text
, school_longName :: Text
......
......@@ -29,6 +29,7 @@ module Gargantext.Prelude
, module Data.Maybe
, round
, sortWith
, module Prelude
)
where
......@@ -63,6 +64,7 @@ import Protolude ( Bool(True, False), Int, Int64, Double, Integer
, panic
)
import Prelude (Enum, Bounded, minBound, maxBound)
-- TODO import functions optimized in Utils.Count
-- import Protolude hiding (head, last, all, any, sum, product, length)
-- import Gargantext.Utils.Count
......
......@@ -20,8 +20,8 @@ module Gargantext.Text.Convert (risPress2csvWrite)
import System.FilePath (FilePath()) -- , takeExtension)
import Gargantext.Prelude
import Gargantext.Text.Parsers.CSV (writeDocs2Csv)
import Gargantext.Text.Parsers (parseFile, FileFormat(..))
import Gargantext.Text.Corpus.Parsers.CSV (writeDocs2Csv)
import Gargantext.Text.Corpus.Parsers (parseFile, FileFormat(..))
risPress2csvWrite :: FilePath -> IO ()
......
{-|
Module : Gargantext.Text.Crawlers
Module : Gargantext.Text.Corpus.API
Description : All crawlers of Gargantext in one file.
Copyright : (c) CNRS, 2017
License : AGPL + CECILL v3
......@@ -11,23 +11,44 @@ Portability : POSIX
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DeriveGeneric #-}
module Gargantext.Text.Crawlers
module Gargantext.Text.Corpus.API
where
{-
import Data.Text (Text)
--import Gargantext.Prelude
import qualified PUBMED as PubMed
data Crawler = PubMed | HAL | Isidore
--{-
import GHC.Generics (Generic)
import Data.Aeson
import Data.Text (Text)
import Gargantext.Prelude
--import qualified PUBMED as PubMed
import Test.QuickCheck.Arbitrary
import Test.QuickCheck (elements)
import Data.Swagger
--import qualified Gargantext.Text.Corpus.API.Isidore as Isidore
data ExternalAPIs = ALL
| PubMed
| HAL
| IsTex
| IsidoreQuery | IsidoreAuth
deriving (Show, Eq, Enum, Bounded, Generic)
instance FromJSON ExternalAPIs
instance ToJSON ExternalAPIs
type Query = Text
externalAPIs :: [ExternalAPIs]
externalAPIs = [minBound..maxBound]
instance Arbitrary ExternalAPIs
where
arbitrary = elements externalAPIs
--{-
instance ToSchema ExternalAPIs
{-
crawl :: Crawler -> Query -> IO [PubMed.Doc]
crawl Pubmed = PubMed.crawler
--}
-}
{-|
Module : Gargantext.Text.Parsers.IsidoreApi
Module : Gargantext.Text.Corpus.API.Isidore
Description : To query French Humanities publication database from its API
Copyright : (c) CNRS, 2019-Present
License : AGPL + CECILL v3
......@@ -13,7 +13,7 @@ Portability : POSIX
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE OverloadedStrings #-}
module Gargantext.Text.Parsers.IsidoreApi where
module Gargantext.Text.Corpus.API.Isidore where
import System.FilePath (FilePath())
import Data.Text (Text)
......@@ -23,10 +23,10 @@ import Gargantext.Prelude
import Isidore.Client
import Servant.Client
import qualified Data.Text as Text
import qualified Gargantext.Text.Parsers.Date as Date
import qualified Gargantext.Text.Corpus.Parsers.Date as Date
import qualified Isidore as Isidore
import Gargantext.Text.Parsers.CSV (writeDocs2Csv)
import Gargantext.Text.Parsers (cleanText)
import Gargantext.Text.Corpus.Parsers.CSV (writeDocs2Csv)
import Gargantext.Text.Corpus.Parsers (cleanText)
-- | TODO work with the ServantErr
get :: Lang -> Maybe Isidore.Limit
......
{-|
Module : Gargantext.Text.Parsers
Module : Gargantext.Text.Corpus.Parsers
Description : All parsers of Gargantext in one file.
Copyright : (c) CNRS, 2017
License : AGPL + CECILL v3
......@@ -22,7 +22,7 @@ please follow the types.
{-# LANGUAGE PackageImports #-}
{-# LANGUAGE OverloadedStrings #-}
module Gargantext.Text.Parsers (FileFormat(..), clean, parseFile, cleanText)
module Gargantext.Text.Corpus.Parsers (FileFormat(..), clean, parseFile, cleanText)
where
--import Data.ByteString (ByteString)
......@@ -48,11 +48,11 @@ import qualified Data.Text as DT
import Gargantext.Core (Lang(..))
import Gargantext.Prelude
import Gargantext.Database.Types.Node (HyperdataDocument(..))
import qualified Gargantext.Text.Parsers.WOS as WOS
import qualified Gargantext.Text.Parsers.RIS as RIS
import Gargantext.Text.Parsers.RIS.Presse (presseEnrich)
import qualified Gargantext.Text.Parsers.Date as Date
import Gargantext.Text.Parsers.CSV (parseHal)
import qualified Gargantext.Text.Corpus.Parsers.WOS as WOS
import qualified Gargantext.Text.Corpus.Parsers.RIS as RIS
import Gargantext.Text.Corpus.Parsers.RIS.Presse (presseEnrich)
import qualified Gargantext.Text.Corpus.Parsers.Date as Date
import Gargantext.Text.Corpus.Parsers.CSV (parseHal)
import Gargantext.Text.Terms.Stop (detectLang)
------------------------------------------------------------------------
......
{-|
Module : Gargantext.Text.Parsers.CSV
Module : Gargantext.Text.Corpus.Parsers.CSV
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
......@@ -15,7 +15,7 @@ CSV parser for Gargantext corpus files.
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DeriveGeneric #-}
module Gargantext.Text.Parsers.CSV where
module Gargantext.Text.Corpus.Parsers.CSV where
import Control.Applicative
import Data.Char (ord)
......
{-|
Module : Gargantext.Text.Parsers.Date
Module : Gargantext.Text.Corpus.Parsers.Date
Description : Some utils to parse dates
Copyright : (c) CNRS 2017-present
License : AGPL + CECILL v3
......@@ -10,7 +10,7 @@ Portability : POSIX
According to the language of the text, parseDateRaw returns date as Text:
TODO : Add some tests
import Gargantext.Text.Parsers.Date as DGP
import Gargantext.Text.Corpus.Parsers.Date as DGP
DGP.parseDateRaw DGP.FR "12 avril 2010" == "2010-04-12T00:00:00.000+00:00"
-}
......@@ -18,7 +18,7 @@ DGP.parseDateRaw DGP.FR "12 avril 2010" == "2010-04-12T00:00:00.000+00:00"
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module Gargantext.Text.Parsers.Date (parse, parseRaw, split) where
module Gargantext.Text.Corpus.Parsers.Date (parse, parseRaw, split) where
import Data.HashMap.Strict as HM hiding (map)
import Data.Text (Text, unpack, splitOn, pack)
......
{-|
Module : Gargantext.Text.Parsers.Date.Attoparsec
Module : Gargantext.Text.Corpus.Parsers.Date.Attoparsec
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
......@@ -13,7 +13,7 @@ Portability : POSIX
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module Gargantext.Text.Parsers.Date.Attoparsec
module Gargantext.Text.Corpus.Parsers.Date.Attoparsec
where
import Control.Applicative ((<*))
......
{-|
Module : Gargantext.Text.Parsers.Date
Module : Gargantext.Text.Corpus.Parsers.Date
Description : Some utils to parse dates
Copyright : (c) CNRS 2017-present
License : AGPL + CECILL v3
......@@ -13,7 +13,7 @@ Portability : POSIX
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module Gargantext.Text.Parsers.Date.Parsec
module Gargantext.Text.Corpus.Parsers.Date.Parsec
where
import Control.Monad ((=<<))
......
{-|
Module : Gargantext.Text.Parsers.GrandDebat
Module : Gargantext.Text.Corpus.Parsers.GrandDebat
Description : Grand Debat Types
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
......@@ -16,7 +16,7 @@ TODO: create a separate Lib.
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleInstances #-}
module Gargantext.Text.Parsers.GrandDebat
module Gargantext.Text.Corpus.Parsers.GrandDebat
where
import GHC.IO (FilePath)
......
{-|
Module : Gargantext.Text.Parsers.Isidore
Module : Gargantext.Text.Corpus.Parsers.Isidore
Description : To query French Humanities publication database
Copyright : (c) CNRS, 2019-Present
License : AGPL + CECILL v3
......@@ -19,7 +19,7 @@ TODO:
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE OverloadedStrings #-}
module Gargantext.Text.Parsers.Isidore where
module Gargantext.Text.Corpus.Parsers.Isidore where
import Control.Lens hiding (contains)
import Data.ByteString.Lazy (ByteString)
......
{-|
Module : Gargantext.Text.Parsers.Json2Csv
Module : Gargantext.Text.Corpus.Parsers.Json2Csv
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
......@@ -17,7 +17,7 @@ Json parser to export towoard CSV GargV3 format.
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TemplateHaskell #-}
module Gargantext.Text.Parsers.Json2Csv (json2csv, readPatents)
module Gargantext.Text.Corpus.Parsers.Json2Csv (json2csv, readPatents)
where
import Prelude (read)
......@@ -28,7 +28,7 @@ import Data.Text (Text, unpack)
import Gargantext.Core.Utils.Prefix (unPrefix)
import Gargantext.Prelude
import System.IO (FilePath)
import Gargantext.Text.Parsers.CSV (CsvDoc(..), writeFile, headerCsvGargV3)
import Gargantext.Text.Corpus.Parsers.CSV (CsvDoc(..), writeFile, headerCsvGargV3)
import Data.Vector (fromList)
data Patent = Patent { _patent_title :: Text
......
{-|
Module : Gargantext.Text.Parsers.RIS
Module : Gargantext.Text.Corpus.Parsers.RIS
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
......@@ -19,7 +19,7 @@ citation programs to exchange data.
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module Gargantext.Text.Parsers.RIS (parser, onField, fieldWith, lines) where
module Gargantext.Text.Corpus.Parsers.RIS (parser, onField, fieldWith, lines) where
import Data.List (lookup)
import Control.Applicative
......
{-|
Module : Gargantext.Text.Parsers.RIS.Presse
Module : Gargantext.Text.Corpus.Parsers.RIS.Presse
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
......@@ -14,7 +14,7 @@ Presse RIS format parser for Europresse Database.
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module Gargantext.Text.Parsers.RIS.Presse (presseEnrich) where
module Gargantext.Text.Corpus.Parsers.RIS.Presse (presseEnrich) where
import Data.List (lookup)
import Data.Either (either)
......@@ -22,9 +22,9 @@ import Data.Tuple.Extra (first, both, uncurry)
import Data.Attoparsec.ByteString (parseOnly)
import Data.ByteString (ByteString, length)
import Gargantext.Prelude hiding (takeWhile, take, length)
import Gargantext.Text.Parsers.RIS (onField)
import Gargantext.Text.Corpus.Parsers.RIS (onField)
import Gargantext.Core (Lang(..))
import qualified Gargantext.Text.Parsers.Date.Attoparsec as Date
import qualified Gargantext.Text.Corpus.Parsers.Date.Attoparsec as Date
......
{-|
Module : Gargantext.Text.Parsers.WOS
Module : Gargantext.Text.Corpus.Parsers.WOS
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
......@@ -14,14 +14,14 @@ commentary with @some markup@.
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module Gargantext.Text.Parsers.WOS (parser, keys) where
module Gargantext.Text.Corpus.Parsers.WOS (parser, keys) where
import Control.Applicative
import Data.Attoparsec.ByteString (Parser, string, takeTill, take, manyTill, many1)
import Data.Attoparsec.ByteString.Char8 (anyChar, isEndOfLine)
import Data.ByteString (ByteString)
import Data.ByteString.Char8 (pack)
import Gargantext.Text.Parsers.RIS (fieldWith)
import Gargantext.Text.Corpus.Parsers.RIS (fieldWith)
import Prelude hiding (takeWhile, take, concat, readFile, lines, concat)
-------------------------------------------------------------
......
{-|
Module : Gargantext.Text.Parsers.WOS
Module : Gargantext.Text.Corpus.Parsers.Wikimedia
Description : Parser for Wikimedia dump
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
......@@ -7,7 +7,7 @@ Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
@Gargantext.Text.Parsers.Wikimedia@:
@Gargantext.Text.Corpus.Parsers.Wikimedia@:
This module provide a parser for wikipedia dump.
This include an xml parser for wikipedia's xml
and an wikimedia to plaintext converter for the wikipedia text field
......@@ -16,7 +16,7 @@ and an wikimedia to plaintext converter for the wikipedia text field
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE NoImplicitPrelude #-}
module Gargantext.Text.Parsers.Wikimedia
module Gargantext.Text.Corpus.Parsers.Wikimedia
where
import Control.Monad.Catch
......
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE NoImplicitPrelude #-}
module Gargantext.Text.Parsers.Isidore where
import Data.Text (Text)
import Data.Either
import Gargantext.Prelude
import Data.Aeson
import Data.Proxy
import GHC.Generics
import Network.HTTP.Client (newManager)
import Network.HTTP.Client.TLS (tlsManagerSettings)
import Servant.API
import Servant.Client
type IsidoreAPI = "sparql" :> Capture "query" Text :> Get '[JSON] [IsidoreDoc]
data IsidoreDoc =
IsidoreDoc {title :: Maybe Text}
deriving (Show, Generic)
instance FromJSON IsidoreDoc
instance ToJSON IsidoreDoc
isidoreDocsApi :: Proxy IsidoreAPI
isidoreDocsApi = Proxy
isidoreDocs :: ClientM [IsidoreDoc]
isidoreDocs = client isidoreDocsApi
getIsidoreDocs :: IO [IsidoreDoc]
getIsidoreDocs = do
manager' <- newManager tlsManagerSettings
res <- runClientM isidoreDocs $ mkClientEnv manager' $ BaseUrl Https "https://www.rechercheisidore.fr" 8080 ""
case res of
Left _ -> panic "err"
Right res' -> pure res'
......@@ -30,7 +30,7 @@ import Data.Text (Text)
import Gargantext.Prelude
import Gargantext.Text.Terms.Mono (monoTexts)
import Gargantext.Text.Terms.Mono.Stem as ST
import Gargantext.Text.Parsers.CSV
import Gargantext.Text.Corpus.Parsers.CSV
type DocId = Int
......
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