esqueleto-textsearch-1.3.1: PostgreSQL full text search for Esqueleto
Safe HaskellSafe-Inferred
LanguageHaskell2010

Database.Esqueleto.TextSearch.Language

Contents

Synopsis

Documentation

(@@.) Source #

Arguments

:: SqlExpr (Value TsVector)

the document to search in

-> SqlExpr (Value (TsQuery Lexemes))

the query made by prefixAndQuery

-> SqlExpr (Value Bool) 

Apply some query to a tsvector document for example:

searchCompany :: SqlExpr (Entity CompanySearchIndex) -> NonEmpty (TsQuery Words) -> SqlQuery ()
searchCompany company term = do
  let query = prefixAndQuery term
      norm = val []
  where_ $ (company ^. CompanySearchIndexDocument) @@. query

prefixAndQuery :: NonEmpty (TsQuery Words) -> SqlExpr (Value (TsQuery Lexemes)) Source #

Deprecated: these functions are simple wrappers for to_tsquery, use that directly instead

format the query into lexemes the result can be used in @@. for example:

searchCompany :: SqlExpr (Entity CompanySearchIndex) -> (NonEmpty (TsQuery Words)) -> SqlQuery ()
searchCompany company term = do
  let query = prefixAndQuery term
      norm = val []
  where_ $ (company ^. CompanySearchIndexDocument) @@. query

this uses && to combine queries

prefixOrQuery :: NonEmpty (TsQuery Words) -> SqlExpr (Value (TsQuery Lexemes)) Source #

Deprecated: these functions are simple wrappers for to_tsquery, use that directly instead

prefixAndQueryLang :: RegConfig -> NonEmpty (TsQuery Words) -> SqlExpr (Value (TsQuery Lexemes)) Source #

Deprecated: these functions are simple wrappers for to_tsquery, use that directly instead

specify a language to be used with the query.

prefixOrQueryLang :: RegConfig -> NonEmpty (TsQuery Words) -> SqlExpr (Value (TsQuery Lexemes)) Source #

Deprecated: these functions are simple wrappers for to_tsquery, use that directly instead

same as prefixAndQueryLang but uses || to combine quereis

toSearchTerm :: Text -> Maybe (NonEmpty (TsQuery Words)) Source #

Constructs a valid search query, removes a bunch of illegal characters and splits the terms for better results. Also checks if there is anything in the search term.

using a search term is optional, but it's probably what you want. all underlying primitives are exposed.

toSearchTermWeighted :: [Weight] -> Text -> Maybe (NonEmpty (TsQuery Words)) Source #

create a search term with some weight, this allows for restricting on specific weighs. see: https://www.postgresql.org/docs/current/textsearch-controls.html#TEXTSEARCH-PARSING-QUERIES use the semigroup instance on search term to combine searchterms.

to_tsquery :: SqlExpr (Value RegConfig) -> SqlExpr (Value (TsQuery Words)) -> SqlExpr (Value (TsQuery Lexemes)) Source #

constructs a lexeme query out of a word algebra english is the internal model used by postgres.

searchCompany :: SqlExpr (Entity CompanySearchIndex) -> Text -> SqlQuery ()
searchCompany company term = do
  let query = to_tsquery (val "english") $ val $ andWords $ toSearchTerm term
  where_ $ (company ^. CompanySearchIndexDocument) @@. query
  

to_tsquery_en :: SqlExpr (Value (TsQuery Words)) -> SqlExpr (Value (TsQuery Lexemes)) Source #

to_tsquery defaulted to english

searchCompany :: SqlExpr (Entity CompanySearchIndex) -> Text -> SqlQuery ()
searchCompany company term = do
  let query = to_tsquery_en $ val $ andWords $ prefixAndQuery term
  where_ $ (company ^. CompanySearchIndexDocument) @@. query
  

ts_rank Source #

Arguments

:: SqlExpr (Value Weights)

relative weighting of a b c and d, see defaultWeights

-> SqlExpr (Value TsVector)

the document to search in

-> SqlExpr (Value (TsQuery Lexemes))

the query made by prefixAndQuery

-> SqlExpr (Value [NormalizationOption])

normalization option to indicate how to deal with document length

-> SqlExpr (Value Double) 

Organize search result by weights. This allows you to put better matching results higher. for example:

searchCompany :: SqlExpr (Entity CompanySearchIndex) -> NonEmpty (TsQuery Words) -> SqlQuery ()
searchCompany company term = do
  let query = prefixAndQuery term
      norm = val []
  where_ $ (company ^. CompanySearchIndexDocument) @@. query
  orderBy [desc (ts_rank (val defaultWeights)
                 (company ^. CompanySearchIndexDocument)
                 query norm)]

ts binary

tsquery_or :: SqlExpr (Value (TsQuery Lexemes)) -> SqlExpr (Value (TsQuery Lexemes)) -> SqlExpr (Value (TsQuery Lexemes)) Source #

(||) for tsquery. This function would be called (&&.) but Esqueleto's (||.) confines that fn to sql boolean expressions.

x::tsquery || y::tsquery == to_tsquery('x | y')

tsquery_and :: SqlExpr (Value (TsQuery Lexemes)) -> SqlExpr (Value (TsQuery Lexemes)) -> SqlExpr (Value (TsQuery Lexemes)) Source #

(&&) for tsquery. This function would be called (&&.) but Esqueleto's (&&.) confines that fn to sql boolean expressions.

x::tsquery && y::tsquery == to_tsquery('x & y')