| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Database.Esqueleto.TextSearch
Description
Haskell bindings for postgres full text search. for a good explenation see https://rachbelaid.com/postgres-full-text-search-is-good-enough/
see the readme for a full tutorial.
Synopsis
- (@@.) :: SqlExpr (Value TsVector) -> SqlExpr (Value (TsQuery Lexemes)) -> SqlExpr (Value Bool)
- prefixAndQuery :: SearchTerm -> SqlExpr (Value (TsQuery Lexemes))
- toSearchTerm :: Text -> Maybe SearchTerm
- data SearchTerm
- ts_rank :: SqlExpr (Value Weights) -> SqlExpr (Value TsVector) -> SqlExpr (Value (TsQuery Lexemes)) -> SqlExpr (Value [NormalizationOption]) -> SqlExpr (Value Double)
- defaultWeights :: Weights
- data Weights = Weights {}
- data RegConfig
- data NormalizationOption
- module Database.Esqueleto.TextSearch.Language
- module Database.Esqueleto.TextSearch.Types
Documentation
Arguments
| :: SqlExpr (Value TsVector) | the document to search in |
| -> SqlExpr (Value (TsQuery Lexemes)) | the query made by |
| -> SqlExpr (Value Bool) |
Apply some query to a tsvector document for example:
searchCompany :: SqlExpr (Entity CompanySearchIndex) -> SearchTerm -> SqlQuery ()
searchCompany company term = do
let query = prefixAndQuery term
norm = val []
where_ $ (company ^. CompanySearchIndexDocument) @@. query
prefixAndQuery :: SearchTerm -> SqlExpr (Value (TsQuery Lexemes)) Source #
format the query into lexemes
the result can be used in @@. for example:
searchCompany :: SqlExpr (Entity CompanySearchIndex) -> SearchTerm -> SqlQuery ()
searchCompany company term = do
let query = prefixAndQuery term
norm = val []
where_ $ (company ^. CompanySearchIndexDocument) @@. query
toSearchTerm :: Text -> Maybe SearchTerm 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.
data SearchTerm Source #
A valid search term.
created with toSearchTerm.
Instances
| Show SearchTerm Source # | |
Defined in Database.Esqueleto.TextSearch.Language Methods showsPrec :: Int -> SearchTerm -> ShowS # show :: SearchTerm -> String # showList :: [SearchTerm] -> ShowS # | |
Arguments
| :: SqlExpr (Value Weights) | relative weighting of a b c and d, see |
| -> SqlExpr (Value TsVector) | the document to search in |
| -> SqlExpr (Value (TsQuery Lexemes)) | the query made by |
| -> 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) -> SearchTerm -> 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)]
Constructors
| Weights | |
Instances
| Show Weights Source # | |
| Eq Weights Source # | |
| PersistField Weights Source # | |
Defined in Database.Esqueleto.TextSearch.Types Methods toPersistValue :: Weights -> PersistValue # | |
| PersistFieldSql Weights Source # | |
regconfig is the object identifier type which represents the text search configuration in Postgres: http://www.postgresql.org/docs/9.3/static/datatype-oid.html
this could for example be a language or simple.
Instances
| IsString RegConfig Source # | |
Defined in Database.Esqueleto.TextSearch.Types Methods fromString :: String -> RegConfig # | |
| Show RegConfig Source # | |
| Eq RegConfig Source # | |
| PersistField RegConfig Source # | |
Defined in Database.Esqueleto.TextSearch.Types Methods toPersistValue :: RegConfig -> PersistValue # | |
| PersistFieldSql RegConfig Source # | |
data NormalizationOption Source #
ranking functions take an integer normalization option that specifies whether and how a document's length should impact its rank. The integer option controls several behaviors, so it is a bit mask: you can specify one or more behaviors using | (for example, 2|4). https://www.postgresql.org/docs/current/textsearch-controls.html#TEXTSEARCH-RANKING
Constructors
| NormNone | 0 (the default) ignores the document length |
| Norm1LogLength | 1 divides the rank by 1 + the logarithm of the document length |
| NormLength | 2 divides the rank by the document length |
| NormMeanHarmDist | 4 divides the rank by the mean harmonic distance between extents (this is implemented only by ts_rank_cd) |
| NormUniqueWords | 8 divides the rank by the number of unique words in document |
| Norm1LogUniqueWords | 16 divides the rank by 1 + the logarithm of the number of unique words in document |
| Norm1Self | 32 divides the rank by itself + 1 |