{-# LANGUAGE CPP #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE OverloadedStrings #-} module Database.Esqueleto.TextSearch.Language ( (@@.) , to_tsvector , to_tsquery , plainto_tsquery , ts_rank , ts_rank_cd , setweight ) where import Data.String (IsString) import Data.Text (Text) import Database.Esqueleto (SqlExpr, Value) #if MIN_VERSION_esqueleto(3,5,0) import Database.Esqueleto.Internal.Internal (unsafeSqlBinOp, unsafeSqlFunction) #else import Database.Esqueleto.Internal.Sql (unsafeSqlBinOp, unsafeSqlFunction) #endif import Database.Esqueleto.TextSearch.Types (@@.) :: SqlExpr (Value TsVector) -> SqlExpr (Value (TsQuery Lexemes)) -> SqlExpr (Value Bool) @@. :: SqlExpr (Value TsVector) -> SqlExpr (Value (TsQuery Lexemes)) -> SqlExpr (Value Bool) (@@.) = forall a b c. Builder -> SqlExpr (Value a) -> SqlExpr (Value b) -> SqlExpr (Value c) unsafeSqlBinOp Builder "@@" to_tsvector :: IsString a => SqlExpr (Value RegConfig) -> SqlExpr (Value a) -> SqlExpr (Value TsVector) to_tsvector :: forall a. IsString a => SqlExpr (Value RegConfig) -> SqlExpr (Value a) -> SqlExpr (Value TsVector) to_tsvector SqlExpr (Value RegConfig) a SqlExpr (Value a) b = forall a b. UnsafeSqlFunctionArgument a => Builder -> a -> SqlExpr (Value b) unsafeSqlFunction Builder "to_tsvector" (SqlExpr (Value RegConfig) a, SqlExpr (Value a) b) to_tsquery :: SqlExpr (Value RegConfig) -> SqlExpr (Value (TsQuery Words)) -> SqlExpr (Value (TsQuery Lexemes) ) to_tsquery :: SqlExpr (Value RegConfig) -> SqlExpr (Value (TsQuery Words)) -> SqlExpr (Value (TsQuery Lexemes)) to_tsquery SqlExpr (Value RegConfig) a SqlExpr (Value (TsQuery Words)) b = forall a b. UnsafeSqlFunctionArgument a => Builder -> a -> SqlExpr (Value b) unsafeSqlFunction Builder "to_tsquery" (SqlExpr (Value RegConfig) a, SqlExpr (Value (TsQuery Words)) b) plainto_tsquery :: SqlExpr (Value RegConfig) -> SqlExpr (Value Text) -> SqlExpr (Value (TsQuery Lexemes)) plainto_tsquery :: SqlExpr (Value RegConfig) -> SqlExpr (Value Text) -> SqlExpr (Value (TsQuery Lexemes)) plainto_tsquery SqlExpr (Value RegConfig) a SqlExpr (Value Text) b = forall a b. UnsafeSqlFunctionArgument a => Builder -> a -> SqlExpr (Value b) unsafeSqlFunction Builder "plainto_tsquery" (SqlExpr (Value RegConfig) a, SqlExpr (Value Text) b) ts_rank :: SqlExpr (Value Weights) -> SqlExpr (Value TsVector) -> SqlExpr (Value (TsQuery Lexemes)) -> SqlExpr (Value [NormalizationOption]) -> SqlExpr (Value Double) ts_rank :: SqlExpr (Value Weights) -> SqlExpr (Value TsVector) -> SqlExpr (Value (TsQuery Lexemes)) -> SqlExpr (Value [NormalizationOption]) -> SqlExpr (Value Double) ts_rank SqlExpr (Value Weights) a SqlExpr (Value TsVector) b SqlExpr (Value (TsQuery Lexemes)) c SqlExpr (Value [NormalizationOption]) d = forall a b. UnsafeSqlFunctionArgument a => Builder -> a -> SqlExpr (Value b) unsafeSqlFunction Builder "ts_rank" (SqlExpr (Value Weights) a, SqlExpr (Value TsVector) b, SqlExpr (Value (TsQuery Lexemes)) c, SqlExpr (Value [NormalizationOption]) d) ts_rank_cd :: 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) ts_rank_cd SqlExpr (Value Weights) a SqlExpr (Value TsVector) b SqlExpr (Value (TsQuery Lexemes)) c SqlExpr (Value [NormalizationOption]) d = forall a b. UnsafeSqlFunctionArgument a => Builder -> a -> SqlExpr (Value b) unsafeSqlFunction Builder "ts_rank_cd" (SqlExpr (Value Weights) a, SqlExpr (Value TsVector) b, SqlExpr (Value (TsQuery Lexemes)) c, SqlExpr (Value [NormalizationOption]) d) setweight :: SqlExpr (Value TsVector) -> SqlExpr (Value Weight) -> SqlExpr (Value TsVector) setweight :: SqlExpr (Value TsVector) -> SqlExpr (Value Weight) -> SqlExpr (Value TsVector) setweight SqlExpr (Value TsVector) a SqlExpr (Value Weight) b = forall a b. UnsafeSqlFunctionArgument a => Builder -> a -> SqlExpr (Value b) unsafeSqlFunction Builder "setweight" (SqlExpr (Value TsVector) a, SqlExpr (Value Weight) b)