]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/Core/Text/Corpus/Query.hs
WIP - Add Gargantext.Core.Text.Corpus.Query
[gargantext.git] / src / Gargantext / Core / Text / Corpus / Query.hs
1 {-# LANGUAGE DerivingStrategies #-}
2 module Gargantext.Core.Text.Corpus.Query (
3 Query -- * opaque
4 , RawQuery(..)
5 , Limit(..)
6 , getQuery
7 , parseQuery
8 , ExternalAPIs(..)
9 ) where
10
11 import Data.Bifunctor
12 import Data.String
13 import Gargantext.API.Admin.Orchestrator.Types
14 import Gargantext.Core.Types
15 import Prelude
16 import qualified Data.Aeson as Aeson
17 import qualified Data.BoolExpr as BoolExpr
18 import qualified Data.BoolExpr.Parser as BoolExpr
19 import qualified Data.Swagger as Swagger
20 import qualified Data.Text as T
21 import qualified Servant.API as Servant
22 import qualified Text.Parsec as P
23
24 -- | A raw query, as typed by the user from the frontend.
25 newtype RawQuery = RawQuery { getRawQuery :: T.Text }
26 deriving newtype ( Show, Eq, IsString
27 , Servant.FromHttpApiData, Servant.ToHttpApiData
28 , Aeson.FromJSON, Aeson.ToJSON
29 , Swagger.ToParamSchema, Swagger.ToSchema)
30
31 -- | A limit to the number of results we want to retrieve.
32 newtype Limit = Limit { getLimit :: Int }
33 deriving newtype ( Show, Eq, Num
34 , Servant.FromHttpApiData, Servant.ToHttpApiData
35 , Aeson.FromJSON, Aeson.ToJSON
36 , Swagger.ToParamSchema, Swagger.ToSchema)
37
38 -- | An opaque wrapper around a 'Query' type which can be parsed from a boolean
39 -- expression like (a AND b) OR c, and which can be interpreted in many ways
40 -- according to the particular service we are targeting.
41 newtype Query = Query { getQuery :: (BoolExpr.CNF Term) }
42 deriving Show
43
44 -- | Parses an input 'Text' into a 'Query', reporting an error if it fails.
45 parseQuery :: RawQuery -> Either String Query
46 parseQuery (RawQuery txt) = bimap show (Query . BoolExpr.boolTreeToCNF) $
47 P.runParser (BoolExpr.parseBoolExpr (Term . T.pack <$> BoolExpr.identifier)) () "Corpus.Query" (T.unpack txt)