{-# OPTIONS_HADDOCK show-extensions #-} {-| Module : Opaleye.TextSearch Description : PostgreSQL Full Text Search support for opaleye Copyright : (c) Gargantext 2024- License : AGPL-3.0-or-later Maintainer : gargantext@iscpif.fr Stability : 0.1.0.0 Portability : POSIX -} module Opaleye.TextSearch ( -- * How to use -- $use -- * Types SqlTSQuery , SqlTSVector -- * Functions and operators , (@@) , pgTSVector , pgTSQuery , sqlTSQuery -- * Various parsing queries -- $parsing_queries , sqlPlainToTSQuery , sqlToTSQuery -- * Internals (mostly) , to_pgTSQuery , plainto_pgTSQuery ) where import Opaleye.Internal.Column (Field) import Opaleye.Internal.PGTypesExternal (SqlText) import Opaleye.SqlTypes (sqlString) import Opaleye.TextSearch.Internal.Types import Opaleye.TextSearch.Operators ((@@)) import qualified Opaleye.Internal.Column as C import qualified Opaleye.Internal.HaskellDB.PrimQuery as HPQ import GHC.RTS.Flags (TraceFlags(user)) {- $use __Example__: @ data MyEntity id text search = MyEntity { _id :: id , _text :: text , _search :: search } deriving ('Show', 'GHC.Generics.Generic') $('Data.Profunctor.Product.TH.makeAdaptorAndInstance' \"pMyEntity\" ''MyEntity) type MyEntityRead = MyEntity ('Field' 'SqlInt4' ) ('Field' 'SqlText' ) ('Field' 'SqlTSVector' ) type MyEntityWrite = MyEntity ('Maybe' ('Field' 'SqlInt4' )) ('Field' 'SqlText' ) ('Field' 'SqlTSVector' ) myEntityTable :: 'Opaleye.Internal.Table' MyEntityWrite MyEntityRead myEntityTable = 'Opaleye.Internal.Table' \"my_entity\" ( pMyEntity MyEntity { _id = 'Opaleye.Internal.Table.optionalTableField' \"id\" , _text = 'Opaleye.Internal.Table.requiredTableField' \"text\" , _search = 'Opaleye.Internal.Table.optionalTableField' \"search_vector\" } ) myQuery :: 'Text' -> 'Opaleye.Internal.Sql.Select' ('Opaleye.Internal.Column.Column' 'SqlInt4', 'Opaleye.Internal.Column' 'SqlText') myQuery q = proc () -> do row <- myEntityTable -< () 'Opaleye.Operators.restrict' -< (_search row) @@ ('sqlPlainToTSQuery' (unpack q)) 'Control.Arrow.returnA' -< (_id row, _text row) 'Opaleye.runSelect' conn (myQuery \"hello world\") @ -} -- Full Text Search -- | PostgreSQL @tsvector@ coercion from text. pgTSVector :: Field SqlText -> Field SqlTSVector pgTSVector (C.Column e) = C.Column (HPQ.FunExpr "tsvector" [e]) -- | PostgreSQL @tsquery@ coercion from text. pgTSQuery :: Field SqlText -> Field SqlTSQuery pgTSQuery (C.Column e) = C.Column (HPQ.FunExpr "tsquery" [e]) -- | Coerce given 'String' to @tsquery@. sqlTSQuery :: String -> Field SqlTSQuery sqlTSQuery = pgTSQuery . sqlString {- $parsing_queries For @to_tsquery@, @plainto_tsquery@, etc. functions, see "Parsing queries" section in [PostgreSQL docs](https://www.postgresql.org/docs/16/textsearch-controls.html#TEXTSEARCH-PARSING-QUERIES) -} -- | Call 'plainto_tsquery'. sqlPlainToTSQuery :: String -> Field SqlTSQuery sqlPlainToTSQuery = plainto_pgTSQuery -- | Call @to_tsquery@ on the input string. sqlToTSQuery :: String -> Field SqlTSQuery sqlToTSQuery = to_pgTSQuery -- | Converts a 'String' into a Postgres' tsQuery by calling @to_tsquery@ on the input string. to_pgTSQuery :: String -> Field SqlTSQuery to_pgTSQuery query = C.Column (HPQ.FunExpr "to_tsquery" [HPQ.ConstExpr (HPQ.StringLit query)]) -- | Converts a 'String' into a Postgres' tsQuery by calling @plainto_tsquery@ on the input string. plainto_pgTSQuery :: String -> Field SqlTSQuery plainto_pgTSQuery query = C.Column (HPQ.FunExpr "plainto_tsquery" [HPQ.ConstExpr (HPQ.StringLit query)])