Commit b14210ab authored by Alexandre Delanoë's avatar Alexandre Delanoë

[FEAT] query search to && bool (thx @np).

parent 50da0736
...@@ -17,51 +17,72 @@ commentary with @some markup@. ...@@ -17,51 +17,72 @@ commentary with @some markup@.
module Gargantext.Database.TextSearch where module Gargantext.Database.TextSearch where
import Prelude (print) import Prelude (print)
import Gargantext (connectGargandb)
import Control.Monad
import Data.Aeson import Data.Aeson
import Data.List (intersperse)
import Data.String (IsString(..))
import Data.Text (Text, words)
import Database.PostgreSQL.Simple import Database.PostgreSQL.Simple
import Control.Applicative import Database.PostgreSQL.Simple.ToField
import Control.Monad
import Data.Text (Text) import Gargantext (connectGargandb)
import Gargantext.Prelude import Gargantext.Prelude
newtype TSQuery = UnsafeTSQuery [Text]
instance IsString TSQuery
where
fromString = UnsafeTSQuery . words . cs
instance ToField TSQuery
where
toField (UnsafeTSQuery xs)
= Many $ intersperse (Plain " && ")
$ map (\q -> Many [ Plain "plainto_tsquery("
, Escape (cs q)
, Plain ")"
]
) xs
type TextQuery= Text
type ParentId = Int type ParentId = Int
type Limit = Int type Limit = Int
type Offset = Int type Offset = Int
data Order = Asc | Desc data Order = Asc | Desc
toQuery :: Order -> Query instance ToField Order
toQuery Asc = "ASC" where
toQuery Desc = "DESC" toField Asc = Plain "ASC"
toField Desc = Plain "DESC"
-- TODO -- TODO
-- FIX fav -- FIX fav
-- ADD ngrams count -- ADD ngrams count
-- TESTS -- TESTS
textSearchQuery :: Order -> Query textSearchQuery :: Query
textSearchQuery o = "SELECT n.id, n.hyperdata -> 'publication_date' \ textSearchQuery = "SELECT n.id, n.hyperdata->'publication_date' \
\ , n.hyperdata -> 'title' \ \ , n.hyperdata->'title' \
\ , n.hyperdata -> 'source' \ \ , n.hyperdata->'source' \
\ , COALESCE(nn.score,null) \ \ , COALESCE(nn.score,null) \
\ FROM nodes n \ \ FROM nodes n \
\ LEFT JOIN nodes_nodes nn ON nn.node2_id = n.id \ \ LEFT JOIN nodes_nodes nn ON nn.node2_id = n.id \
\ WHERE \ \ WHERE \
\ n.title_abstract @@ to_tsquery(?) \ \ n.title_abstract @@ (?::tsquery) \
\ AND n.parent_id = ? AND n.typename = 4 \ \ AND n.parent_id = ? AND n.typename = 4 \
\ ORDER BY n.hyperdata -> 'publication_date' " \ ORDER BY n.hyperdata -> 'publication_date' ? \
<> toQuery o <> " offset ? limit ?;" \ offset ? limit ?;"
textSearch :: Connection textSearch :: Connection
-> TextQuery -> ParentId -> TSQuery -> ParentId
-> Limit -> Offset -> Order -> Limit -> Offset -> Order
-> IO [(Int,Value,Value,Value, Maybe Int)] -> IO [(Int,Value,Value,Value, Maybe Int)]
textSearch conn q p l o ord = query conn (textSearchQuery ord) (q,p,o,l) textSearch conn q p l o ord = query conn textSearchQuery (q,p,ord, o,l)
textSearchTest :: TextQuery -> IO () textSearchTest :: TSQuery -> IO ()
textSearchTest q = connectGargandb "gargantext.ini" textSearchTest q = connectGargandb "gargantext.ini"
>>= \conn -> textSearch conn q 421968 10 0 Asc >>= \conn -> textSearch conn q 421968 10 0 Asc
>>= mapM_ print >>= mapM_ print
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