Commit 5ae60a4b authored by Alexandre Delanoë's avatar Alexandre Delanoë

[FACTO] Type Class and some Instances : Flow Corpus.

parent 3e2f5b28
...@@ -48,6 +48,7 @@ library: ...@@ -48,6 +48,7 @@ library:
- Gargantext.Text - Gargantext.Text
- Gargantext.Text.Context - Gargantext.Text.Context
- Gargantext.Text.Corpus.Parsers - Gargantext.Text.Corpus.Parsers
- Gargantext.Text.Corpus.API
- Gargantext.Text.Corpus.Parsers.CSV - Gargantext.Text.Corpus.Parsers.CSV
- Gargantext.Text.Examples - Gargantext.Text.Examples
- Gargantext.Text.List.CSV - Gargantext.Text.List.CSV
......
...@@ -33,7 +33,6 @@ import Gargantext.Core.Utils.Prefix (unPrefix) ...@@ -33,7 +33,6 @@ import Gargantext.Core.Utils.Prefix (unPrefix)
import Gargantext.Database.Flow (flowCorpusSearchInDatabase) import Gargantext.Database.Flow (flowCorpusSearchInDatabase)
import Gargantext.Database.Types.Node (CorpusId) import Gargantext.Database.Types.Node (CorpusId)
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Prelude.Utils (hash)
import Servant import Servant
import Test.QuickCheck (elements) import Test.QuickCheck (elements)
import Test.QuickCheck.Arbitrary import Test.QuickCheck.Arbitrary
...@@ -43,7 +42,7 @@ import Gargantext.Database.Types.Node (UserId) ...@@ -43,7 +42,7 @@ import Gargantext.Database.Types.Node (UserId)
data Query = Query { query_query :: Text data Query = Query { query_query :: Text
, query_corpus_id :: Int , query_corpus_id :: Int
, query_files_id :: [Text] , query_databases :: [API.ExternalAPIs]
} }
deriving (Eq, Show, Generic) deriving (Eq, Show, Generic)
...@@ -54,7 +53,7 @@ instance Arbitrary Query where ...@@ -54,7 +53,7 @@ instance Arbitrary Query where
arbitrary = elements [ Query q n fs arbitrary = elements [ Query q n fs
| q <- ["a","b"] | q <- ["a","b"]
, n <- [0..10] , n <- [0..10]
, fs <- map (map hash) [["a","b"], ["c","d"]] , fs <- take 3 $ repeat API.externalAPIs
] ]
instance ToSchema Query where instance ToSchema Query where
...@@ -62,19 +61,20 @@ instance ToSchema Query where ...@@ -62,19 +61,20 @@ instance ToSchema Query where
genericDeclareNamedSchema genericDeclareNamedSchema
defaultSchemaOptions {fieldLabelModifier = \fieldLabel -> drop 6 fieldLabel} defaultSchemaOptions {fieldLabelModifier = \fieldLabel -> drop 6 fieldLabel}
type Api = Summary "New Corpus endpoint" type Api = Summary "New Corpus endpoint"
:> ReqBody '[JSON] Query :> ReqBody '[JSON] Query
:> Post '[JSON] CorpusId :> Post '[JSON] CorpusId
:<|> Get '[JSON] ApiInfo :<|> Get '[JSON] ApiInfo
-- | TODO manage several apis
api :: FlowCmdM env err m => Query -> m CorpusId api :: FlowCmdM env err m => Query -> m CorpusId
api (Query q _ _) = do api (Query q _ as) = do
cId <- flowCorpusSearchInDatabase "user1" EN q cId <- case head as of
pure cId Nothing -> flowCorpusSearchInDatabase "user1" EN q
Just API.All -> flowCorpusSearchInDatabase "user1" EN q
Just _ -> undefined
pure cId
------------------------------------------------ ------------------------------------------------
data ApiInfo = ApiInfo { api_info :: [API.ExternalAPIs]} data ApiInfo = ApiInfo { api_info :: [API.ExternalAPIs]}
...@@ -90,3 +90,4 @@ info :: FlowCmdM env err m => UserId -> m ApiInfo ...@@ -90,3 +90,4 @@ info :: FlowCmdM env err m => UserId -> m ApiInfo
info _u = pure $ ApiInfo API.externalAPIs info _u = pure $ ApiInfo API.externalAPIs
...@@ -12,6 +12,8 @@ Portability : POSIX ...@@ -12,6 +12,8 @@ Portability : POSIX
module Gargantext.Core module Gargantext.Core
where where
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- | Language of a Text -- | Language of a Text
-- For simplicity, we suppose text has an homogenous language -- For simplicity, we suppose text has an homogenous language
......
{-|
Module : Gargantext.Core.Flow
Description : Core Flow main Types
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ConstrainedClassMethods #-}
module Gargantext.Core.Flow where
import Control.Lens ((^.), view, Lens', _Just)
import Data.Map (Map)
import Data.Text (Text)
import Gargantext.Text.Terms (TermType)
import Gargantext.Core (Lang)
import Gargantext.Database.Schema.Ngrams (Ngrams, NgramsType)
import Gargantext.Core.Types.Main (HashId)
import Gargantext.Database.Types.Node -- (HyperdataDocument(..))
import Gargantext.Database.Node.Contact -- (HyperdataContact(..))
import Gargantext.Database.Node.Document.Insert (AddUniqId, InsertDb)
import Gargantext.Database.Utils (Cmd, CmdM)
type FlowCorpus a = ( AddUniqId a
, UniqId a
, InsertDb a
, ExtractNgramsT a
, HasText a
)
class UniqId a
where
uniqId :: Lens' a (Maybe HashId)
class ExtractNgramsT h
where
extractNgramsT :: HasText h => TermType Lang -> h -> Cmd err (Map Ngrams (Map NgramsType Int))
class HasText h
where
hasText :: h -> [Text]
------------------------------------------------------------------------
instance UniqId HyperdataDocument
where
uniqId = hyperdataDocument_uniqId
instance UniqId HyperdataContact
where
uniqId = hc_uniqId
...@@ -18,20 +18,23 @@ Portability : POSIX ...@@ -18,20 +18,23 @@ Portability : POSIX
-} -}
{-# LANGUAGE ConstraintKinds #-} {-# OPTIONS_GHC -fno-warn-orphans #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE InstanceSigs #-} {-# LANGUAGE RankNTypes #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ConstrainedClassMethods #-} {-# LANGUAGE ConstrainedClassMethods #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module Gargantext.Database.Flow -- (flowDatabase, ngrams2list) module Gargantext.Database.Flow -- (flowDatabase, ngrams2list)
where where
import Prelude (String) import Prelude (String)
import Debug.Trace (trace) import Debug.Trace (trace)
import Control.Lens ((^.), view, Lens', _Just) import Control.Lens ((^.), view, _Just)
import Control.Monad (mapM_) import Control.Monad (mapM_)
import Control.Monad.IO.Class (liftIO) import Control.Monad.IO.Class (liftIO)
import Data.List (concat) import Data.List (concat)
...@@ -45,6 +48,7 @@ import Gargantext.API.Ngrams (NgramsElement(..), putListNgrams, RepoCmdM) ...@@ -45,6 +48,7 @@ import Gargantext.API.Ngrams (NgramsElement(..), putListNgrams, RepoCmdM)
import Gargantext.Core (Lang(..)) import Gargantext.Core (Lang(..))
import Gargantext.Core.Types (NodePoly(..), Terms(..)) import Gargantext.Core.Types (NodePoly(..), Terms(..))
import Gargantext.Core.Types.Individu (Username) import Gargantext.Core.Types.Individu (Username)
import Gargantext.Core.Flow
import Gargantext.Core.Types.Main import Gargantext.Core.Types.Main
import Gargantext.Database.Config (userMaster, corpusMasterName) import Gargantext.Database.Config (userMaster, corpusMasterName)
import Gargantext.Database.Flow.Utils (insertDocNgrams) import Gargantext.Database.Flow.Utils (insertDocNgrams)
...@@ -81,13 +85,6 @@ type FlowCmdM env err m = ...@@ -81,13 +85,6 @@ type FlowCmdM env err m =
, HasRepoVar env , HasRepoVar env
) )
type FlowCorpus a = ( AddUniqId a
, UniqId a
, InsertDb a
, ExtractNgramsT a
, HasText a
)
------------------------------------------------------------------------ ------------------------------------------------------------------------
data ApiQuery = ApiIsidoreQuery Text | ApiIsidoreAuth Text data ApiQuery = ApiIsidoreQuery Text | ApiIsidoreAuth Text
...@@ -280,19 +277,6 @@ getOrMkRootWithCorpus username cName c = do ...@@ -280,19 +277,6 @@ getOrMkRootWithCorpus username cName c = do
------------------------------------------------------------------------ ------------------------------------------------------------------------
class UniqId a
where
uniqId :: Lens' a (Maybe HashId)
instance UniqId HyperdataDocument
where
uniqId = hyperdataDocument_uniqId
instance UniqId HyperdataContact
where
uniqId = hc_uniqId
viewUniqId' :: UniqId a => a -> (HashId, a) viewUniqId' :: UniqId a => a -> (HashId, a)
viewUniqId' d = maybe err (\h -> (h,d)) (view uniqId d) viewUniqId' d = maybe err (\h -> (h,d)) (view uniqId d)
where where
...@@ -328,14 +312,6 @@ data DocumentIdWithNgrams a = DocumentIdWithNgrams ...@@ -328,14 +312,6 @@ data DocumentIdWithNgrams a = DocumentIdWithNgrams
} deriving (Show) } deriving (Show)
class ExtractNgramsT h
where
extractNgramsT :: HasText h => TermType Lang -> h -> Cmd err (Map Ngrams (Map NgramsType Int))
class HasText h
where
hasText :: h -> [Text]
instance HasText HyperdataContact instance HasText HyperdataContact
where where
hasText = undefined hasText = undefined
......
...@@ -16,29 +16,30 @@ Portability : POSIX ...@@ -16,29 +16,30 @@ Portability : POSIX
module Gargantext.Text.Corpus.API module Gargantext.Text.Corpus.API
where where
--{-
import GHC.Generics (Generic) import GHC.Generics (Generic)
import Data.Aeson import Data.Aeson
import Data.Text (Text) import Data.Text (Text)
import Gargantext.Prelude import Gargantext.Prelude
--import qualified PUBMED as PubMed import Gargantext.Core (Lang(..))
import Gargantext.Core.Flow (FlowCorpus)
import Gargantext.Database.Types.Node (HyperdataDocument)
import Test.QuickCheck.Arbitrary import Test.QuickCheck.Arbitrary
import Test.QuickCheck (elements) import Test.QuickCheck (elements)
import Data.Swagger import Data.Swagger
--import qualified Gargantext.Text.Corpus.API.Isidore as Isidore
import qualified PUBMED as PubMed
import qualified PUBMED.Parser as Doc (PubMed)
import qualified Gargantext.Text.Corpus.API.Isidore as Isidore
data ExternalAPIs = ALL data ExternalAPIs = All
| PubMed | PubMed
| HAL | HAL
| IsTex -- | IsTex
| IsidoreQuery | IsidoreAuth | IsidoreQuery | IsidoreAuth
deriving (Show, Eq, Enum, Bounded, Generic) deriving (Show, Eq, Enum, Bounded, Generic)
instance FromJSON ExternalAPIs instance FromJSON ExternalAPIs
instance ToJSON ExternalAPIs instance ToJSON ExternalAPIs
type Query = Text
externalAPIs :: [ExternalAPIs] externalAPIs :: [ExternalAPIs]
externalAPIs = [minBound..maxBound] externalAPIs = [minBound..maxBound]
...@@ -48,7 +49,14 @@ instance Arbitrary ExternalAPIs ...@@ -48,7 +49,14 @@ instance Arbitrary ExternalAPIs
arbitrary = elements externalAPIs arbitrary = elements externalAPIs
instance ToSchema ExternalAPIs instance ToSchema ExternalAPIs
{-
crawl :: Crawler -> Query -> IO [PubMed.Doc] type Query = Text
crawl Pubmed = PubMed.crawler type Limit = PubMed.Limit
--}
get :: FlowCorpus a => ExternalAPIs -> Query -> Maybe Limit -> IO [a]
get PubMed q l = either (\e -> panic $ "CRAWL: PubMed" <> e) (map (toDoc EN)) <$> PubMed.crawler q l
get _ _ _ = undefined
toDoc :: FlowCorpus a => Lang -> Doc.PubMed -> a
toDoc = undefined
...@@ -23,7 +23,7 @@ extra-deps: ...@@ -23,7 +23,7 @@ extra-deps:
- git: https://github.com/robstewart57/rdf4h.git - git: https://github.com/robstewart57/rdf4h.git
commit: 4fd2edf30c141600ffad6d730cc4c1c08a6dbce4 commit: 4fd2edf30c141600ffad6d730cc4c1c08a6dbce4
- git: https://gitlab.iscpif.fr/gargantext/crawlers/pubmed.git - git: https://gitlab.iscpif.fr/gargantext/crawlers/pubmed.git
commit: dcaa0f5dd53f20648f4f5a615d29163582a4219c commit: 06476735cb45c704079f548ac5de9d4ba09cf3fb
- git: https://gitlab.iscpif.fr/gargantext/crawlers/hal.git - git: https://gitlab.iscpif.fr/gargantext/crawlers/hal.git
commit: bf57642f6b66f554fdc0a38ac391cd8200dffcb3 commit: bf57642f6b66f554fdc0a38ac391cd8200dffcb3
- git: https://gitlab.iscpif.fr/gargantext/patches-class - git: https://gitlab.iscpif.fr/gargantext/patches-class
......
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