| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Data.TCache.IndexText
Description
Implements full text indexation (indexText) and text search(contains), as an addition to
the query language implemented in IndexQuery
it also can index the lists of elements in a field (with indexList)
so that it is possible to ask for the registers that contains a given element
in the given field (with containsElem)
An example of full text search and element search in a list in combination
using the .&&. operator defined in "indexQuery".
before and after the update of the register
data Doc= Doc{title :: String , authors :: [String], body :: String} deriving (Read,Show, Typeable)
instance Indexable Doc where
key Doc{title=t}= t
instance Serializable Doc where
serialize= pack . show
deserialize= read . unpack
main= do
indexText body T.pack
indexList authors (map T.pack)
let doc= Doc{title= "title", authors=["john","Lewis"], body= "Hi, how are you"}
rdoc <- atomically $ newDBRef doc
r0 <- atomically $ select title $ authors `containsElem` "Lewis"
print r0
r1 <- atomically $ select title $ body `contains` "how are you"
print r1
r2 <- atomically $ select body $ body `contains` "how are you" .&&. authors containsElem "john"
print r2
atomically $ writeDBRef rdoc doc{ body= "what's up"}
r3 <- atomically $ select title $ body `contains` "how are you"
print r3
if r0== r1 && r1== [title doc] then print "OK" else print "FAIL"
if r3== [] then print "OK" else print "FAIL"
Synopsis
- indexText :: (IResource a, Typeable a, Typeable b) => (a -> b) -> (b -> Text) -> IO ()
- indexList :: (IResource a, Typeable a, Typeable b) => (a -> b) -> (b -> [Text]) -> IO ()
- contains :: (IResource a, Typeable a, Typeable b) => (a -> b) -> String -> STM [DBRef a]
- containsElem :: (IResource a, Typeable a, Typeable b) => (a -> b) -> String -> STM [DBRef a]
- allElemsOf :: (IResource a, Typeable a, Typeable b) => (a -> b) -> STM [Text]
Documentation
Arguments
| :: (IResource a, Typeable a, Typeable b) | |
| => (a -> b) | field to index |
| -> (b -> Text) | method to convert the field content to lazy Text (for example |
| -> IO () |
start a trigger to index the contents of a register field
Arguments
| :: (IResource a, Typeable a, Typeable b) | |
| => (a -> b) | field to index |
| -> (b -> [Text]) | method to convert a field element to Text (for example `pack . show` in case of elemets with Show instances) |
| -> IO () |
trigger the indexation of list fields with elements convertible to Text
Arguments
| :: (IResource a, Typeable a, Typeable b) | |
| => (a -> b) | field to search in |
| -> String | text to search |
| -> STM [DBRef a] |
return the DBRefs whose fields include all the words in the requested text contents.Except the words with less than three characters that are not digits or uppercase, that are filtered out before making the query