| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Database.Esqueleto.TextSearch.Language
Synopsis
- (@@.) :: SqlExpr (Value TsVector) -> SqlExpr (Value (TsQuery Lexemes)) -> SqlExpr (Value Bool)
- prefixAndQuery :: SearchTerm -> SqlExpr (Value (TsQuery Lexemes))
- toSearchTerm :: Text -> Maybe SearchTerm
- data SearchTerm
- to_tsvector :: IsString a => SqlExpr (Value RegConfig) -> SqlExpr (Value a) -> SqlExpr (Value TsVector)
- to_tsquery :: SqlExpr (Value RegConfig) -> SqlExpr (Value (TsQuery Words)) -> SqlExpr (Value (TsQuery Lexemes))
- plainto_tsquery :: SqlExpr (Value RegConfig) -> SqlExpr (Value Text) -> SqlExpr (Value (TsQuery Lexemes))
- ts_rank :: SqlExpr (Value Weights) -> SqlExpr (Value TsVector) -> SqlExpr (Value (TsQuery Lexemes)) -> SqlExpr (Value [NormalizationOption]) -> SqlExpr (Value Double)
- ts_rank_cd :: SqlExpr (Value Weights) -> SqlExpr (Value TsVector) -> SqlExpr (Value (TsQuery Lexemes)) -> SqlExpr (Value [NormalizationOption]) -> SqlExpr (Value Double)
- setweight :: SqlExpr (Value TsVector) -> SqlExpr (Value Weight) -> SqlExpr (Value TsVector)
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 # | |
to_tsvector :: IsString a => SqlExpr (Value RegConfig) -> SqlExpr (Value a) -> SqlExpr (Value TsVector) Source #
to_tsquery :: SqlExpr (Value RegConfig) -> SqlExpr (Value (TsQuery Words)) -> SqlExpr (Value (TsQuery Lexemes)) Source #
plainto_tsquery :: SqlExpr (Value RegConfig) -> SqlExpr (Value Text) -> SqlExpr (Value (TsQuery Lexemes)) Source #
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)]