Commit 9173f8b3 authored by Alfredo Di Napoli's avatar Alfredo Di Napoli

Implement conversion from Query to Arxiv

parent b45714a8
...@@ -17,13 +17,14 @@ module Gargantext.Core.Text.Corpus.API.Arxiv ...@@ -17,13 +17,14 @@ module Gargantext.Core.Text.Corpus.API.Arxiv
import Conduit import Conduit
import Data.Maybe import Data.Maybe
import Data.Text (Text) import Data.Text (Text, unpack)
import qualified Data.Text as Text import qualified Data.Text as Text
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Core (Lang(..)) import Gargantext.Core (Lang(..))
import Gargantext.Database.Admin.Types.Hyperdata (HyperdataDocument(..)) import Gargantext.Database.Admin.Types.Hyperdata (HyperdataDocument(..))
import Gargantext.Core.Text.Corpus.Query as Corpus import Gargantext.Core.Text.Corpus.Query as Corpus
import Gargantext.Core.Types (Term(..))
import qualified Arxiv as Arxiv import qualified Arxiv as Arxiv
import qualified Network.Api.Arxiv as Ax import qualified Network.Api.Arxiv as Ax
...@@ -31,7 +32,38 @@ import qualified Network.Api.Arxiv as Ax ...@@ -31,7 +32,38 @@ import qualified Network.Api.Arxiv as Ax
-- | Converts a Gargantext's generic boolean query into an Arxiv Query. -- | Converts a Gargantext's generic boolean query into an Arxiv Query.
convertQuery :: Corpus.Query -> Ax.Query convertQuery :: Corpus.Query -> Ax.Query
convertQuery _q = undefined convertQuery q = mkQuery (interpretQuery q transformAST)
where
transformAST :: BoolExpr Term -> Maybe Ax.Expression
transformAST ast = case ast of
BAnd sub (BConst (Negative term))
-- The second term become positive, so that it can be translated.
-> Ax.AndNot <$> (transformAST sub) <*> transformAST (BConst (Positive term))
BAnd term1 (BNot term2)
-> Ax.AndNot <$> transformAST term1 <*> transformAST term2
BAnd sub1 sub2
-> Ax.And <$> transformAST sub1 <*> transformAST sub2
BOr sub1 sub2
-> Ax.Or <$> transformAST sub1 <*> transformAST sub2
BNot (BConst (Negative term))
-> transformAST (BConst (Positive term)) -- double negation
BNot _
-> Nothing
BTrue
-> Nothing
BFalse
-> Nothing
BConst (Positive (Term term))
-> Just $ Ax.Exp $ Ax.Abs [unpack term]
-- Do not handle negative terms, because we don't have a way to represent them in Arxiv.
BConst (Negative _)
-> Nothing
mkQuery :: Maybe Ax.Expression -> Ax.Query
mkQuery mb_exp = Ax.Query { Ax.qExp = mb_exp
, Ax.qIds = []
, Ax.qStart = 0
, Ax.qItems = Arxiv.batchSize }
-- | TODO put default pubmed query in gargantext.ini -- | TODO put default pubmed query in gargantext.ini
-- by default: 10K docs -- by default: 10K docs
......
...@@ -7,7 +7,9 @@ module Gargantext.Core.Text.Corpus.Query ( ...@@ -7,7 +7,9 @@ module Gargantext.Core.Text.Corpus.Query (
, getQuery , getQuery
, parseQuery , parseQuery
, renderQuery , renderQuery
, interpretQuery
, ExternalAPIs(..) , ExternalAPIs(..)
, module BoolExpr
-- * Useful for testing -- * Useful for testing
, unsafeMkQuery , unsafeMkQuery
...@@ -20,9 +22,9 @@ import Gargantext.Core.Types ...@@ -20,9 +22,9 @@ import Gargantext.Core.Types
import Prelude import Prelude
import Text.ParserCombinators.Parsec import Text.ParserCombinators.Parsec
import qualified Data.Aeson as Aeson import qualified Data.Aeson as Aeson
import qualified Data.BoolExpr as BoolExpr import Data.BoolExpr as BoolExpr
import qualified Data.BoolExpr.Parser as BoolExpr import Data.BoolExpr.Parser as BoolExpr
import qualified Data.BoolExpr.Printer as BoolExpr import Data.BoolExpr.Printer as BoolExpr
import qualified Data.Swagger as Swagger import qualified Data.Swagger as Swagger
import qualified Data.Text as T import qualified Data.Text as T
import qualified Servant.API as Servant import qualified Servant.API as Servant
...@@ -48,6 +50,9 @@ newtype Limit = Limit { getLimit :: Int } ...@@ -48,6 +50,9 @@ newtype Limit = Limit { getLimit :: Int }
newtype Query = Query { getQuery :: (BoolExpr.CNF Term) } newtype Query = Query { getQuery :: (BoolExpr.CNF Term) }
deriving Show deriving Show
interpretQuery :: Query -> (BoolExpr.BoolExpr Term -> ast) -> ast
interpretQuery (Query q) transform = transform (BoolExpr.fromCNF q)
unsafeMkQuery :: BoolExpr.BoolExpr Term -> Query unsafeMkQuery :: BoolExpr.BoolExpr Term -> Query
unsafeMkQuery = Query . BoolExpr.boolTreeToCNF unsafeMkQuery = Query . BoolExpr.boolTreeToCNF
......
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