TCache-0.12.1: A Transactional cache with user-defined persistence

Safe HaskellNone
LanguageHaskell98

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

Documentation

indexText Source #

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 pack in case of String fields). This permits to index non Textual fields

-> IO () 

start a trigger to index the contents of a register field

indexList Source #

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

contains Source #

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

containsElem :: (IResource a, Typeable a, Typeable b) => (a -> b) -> String -> STM [DBRef a] Source #

return the DBRefs of the registers whose field (first parameter, usually a container) contains the requested value.

allElemsOf :: (IResource a, Typeable a, Typeable b) => (a -> b) -> STM [Text] Source #

return all the values of a given field (if it has been indexed with index)