Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Database.Esqueleto.TextSearch.Types
Synopsis
- data TsQuery (a :: QueryType) where
- type Words = 'Words
- type Lexemes = 'Lexemes
- data TsVector
- defaultTsVector :: TsVector
- data RegConfig
- data NormalizationOption
- data Weight
- defaultWeights :: Weights
- data Weights = Weights {}
- data Position
- word :: Text -> TsQuery Words
- queryToText :: TsQuery a -> Text
- textToQuery :: Text -> Either ParseError (TsQuery Lexemes)
Documentation
data TsQuery (a :: QueryType) where Source #
Constructors
Lexeme :: Position -> [Weight] -> Text -> TsQuery Lexemes | |
Word :: Position -> [Weight] -> Text -> TsQuery Words | |
(:&) :: TsQuery a -> TsQuery a -> TsQuery a infixr 3 | |
(:|) :: TsQuery a -> TsQuery a -> TsQuery a infixr 2 | |
Not :: TsQuery a -> TsQuery a |
Instances
a ~ Words => IsString (TsQuery a) Source # | |
Defined in Database.Esqueleto.TextSearch.Types Methods fromString :: String -> TsQuery a # | |
Show (TsQuery a) Source # | |
Eq (TsQuery a) Source # | |
PersistField (TsQuery Lexemes) Source # | |
Defined in Database.Esqueleto.TextSearch.Types Methods toPersistValue :: TsQuery Lexemes -> PersistValue # fromPersistValue :: PersistValue -> Either Text (TsQuery Lexemes) # | |
PersistField (TsQuery Words) Source # | |
Defined in Database.Esqueleto.TextSearch.Types Methods toPersistValue :: TsQuery Words -> PersistValue # fromPersistValue :: PersistValue -> Either Text (TsQuery Words) # | |
PersistFieldSql (TsQuery Lexemes) Source # | |
PersistFieldSql (TsQuery Words) Source # | |
Instances
IsString TsVector Source # | |
Defined in Database.Esqueleto.TextSearch.Types Methods fromString :: String -> TsVector # | |
Show TsVector Source # | |
Eq TsVector Source # | |
PersistField TsVector Source # | |
Defined in Database.Esqueleto.TextSearch.Types Methods toPersistValue :: TsVector -> PersistValue # | |
PersistFieldSql TsVector 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 #
Constructors
NormNone | |
Norm1LogLength | |
NormLength | |
NormMeanHarmDist | |
NormUniqueWords | |
Norm1LogUniqueWords | |
Norm1Self |
Instances
Instances
Show Weight Source # | |
Eq Weight Source # | |
PersistField Weight Source # | |
Defined in Database.Esqueleto.TextSearch.Types Methods toPersistValue :: Weight -> PersistValue # | |
PersistFieldSql Weight Source # | |
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 # | |
queryToText :: TsQuery a -> Text Source #
textToQuery :: Text -> Either ParseError (TsQuery Lexemes) Source #