Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module provides a split searcher and seeker, a simple server-client version of the search in which searcher runs in the background and can communicate
with clients using named pipes. The searcher reads input as a UTF8 encoded bytestring from one named pipe and outputs the search results to another named
pipe. It quits when it receives an empty bytestring as input. The main function for starting the server is runSearch
while a simple client is provided by
askSearcher
. One motivation for this is be able to use this library as search backend for some searches in Emacs (though the implementation may have to wait
for a massive improvement in my elisp skills).
Synopsis
- data SearchResult = SearchResult {}
- query :: Lens' SearchResult (Maybe Text)
- allMatches :: Lens' SearchResult (Vector Int)
- matches :: Lens' SearchResult (Vector [Text])
- data IOPipes = IOPipes {}
- data SearchFunctions a = SearchFunctions {}
- makeMatcher :: forall a. Lens' (SearchFunctions a) (Text -> Maybe (Matcher a))
- lister :: forall a n. KnownNat n => SimpleGetter (SearchFunctions a) (MatcherSized n a -> Vector Text -> Vector Int -> (Vector Int, Vector (Indices n)))
- displayer :: forall a n. KnownNat n => SimpleGetter (SearchFunctions a) (MatcherSized n a -> Text -> Vector n Int -> [Text])
- searchFunctionsOL :: SearchFunctions Int
- searchFunctionsFuzzy :: SearchFunctions MatchPart
- searchLoop :: SearchFunctions a -> (Handle -> [Text] -> IO ()) -> Vector Text -> IO ()
- runSearch :: SearchFunctions a -> (Handle -> [Text] -> IO ()) -> Vector Text -> IO ()
- runSearchStdIn :: SearchFunctions a -> (Handle -> [Text] -> IO ()) -> IO ()
- runSearchStdInDef :: SearchFunctions a -> IO ()
- runSearchStdInColor :: SearchFunctions a -> IO ()
- showMatch :: Handle -> [Text] -> IO ()
- showMatchColor :: Handle -> [Text] -> IO ()
- askSearcher :: String -> String -> Text -> IO ()
- run :: IO ()
- run' :: [String] -> IO ()
- response :: SearchFunctions a -> Vector Text -> Text -> SearchResult -> SearchResult
- event :: SearchFunctions a -> (Handle -> [Text] -> IO ()) -> IOPipes -> Vector Text -> SearchResult -> IO (Maybe SearchResult)
- withIOPipes :: (IOPipes -> IO a) -> IO a
- send :: String -> Text -> IO ()
- recieve :: String -> IO ()
- searchWithMatcher :: SearchFunctions a -> Vector Text -> Maybe Text -> Vector Int -> (Vector Int, (Int, Vector [Text]))
- readVectorStdIn :: IO (Vector Text)
- readVectorHandle :: Handle -> IO (Vector Text)
- readVectorHandleWith :: (Text -> Text) -> (Vector Text -> Vector Text) -> Handle -> IO (Vector Text)
- emptyIndices :: Int -> Vector (Indices 0)
Types and Lenses
data SearchResult Source #
Instances
Eq SearchResult Source # | |
Defined in Talash.Piped (==) :: SearchResult -> SearchResult -> Bool # (/=) :: SearchResult -> SearchResult -> Bool # | |
Show SearchResult Source # | |
Defined in Talash.Piped showsPrec :: Int -> SearchResult -> ShowS # show :: SearchResult -> String # showList :: [SearchResult] -> ShowS # |
allMatches :: Lens' SearchResult (Vector Int) Source #
data SearchFunctions a Source #
SearchFunctions | |
|
makeMatcher :: forall a. Lens' (SearchFunctions a) (Text -> Maybe (Matcher a)) Source #
lister :: forall a n. KnownNat n => SimpleGetter (SearchFunctions a) (MatcherSized n a -> Vector Text -> Vector Int -> (Vector Int, Vector (Indices n))) Source #
displayer :: forall a n. KnownNat n => SimpleGetter (SearchFunctions a) (MatcherSized n a -> Text -> Vector n Int -> [Text]) Source #
searchFunctionsOL :: SearchFunctions Int Source #
Search functions that match the words in i.e. space separated substring in any order. "talash best"
will match "be as"
with the split
["tal","as","h","be","st"]
but "talash best" will not match "bet"
.
searchFunctionsFuzzy :: SearchFunctions MatchPart Source #
Search functions suitable for fuzzy matching. The candidate c
will match the query s
if c
contains all the characters in s
in order. In general there
can be several ways of matching. This tries to find a match with the minimum number of parts. It does not find the minimum number of parts, if that requires
reducing the extent of the partial match during search. E.g. matching "as"
against "talash"
the split will be ["tal","as","h"]
and not
["t","a","la","s","h"]
. While matching "talash best match testing hat"
against "tea"
will not result in ["talash best match ","te","sting h","a","t"]
since
"te"
occurs only after we have match all three letters and we can't know if we will find the "a"
without going through the string.
Searcher
searchLoop :: SearchFunctions a -> (Handle -> [Text] -> IO ()) -> Vector Text -> IO () Source #
Starts with the dummy initialSearchResult
and handles event
in a loop until the searcher receives an empty input and exits.
runSearch :: SearchFunctions a -> (Handle -> [Text] -> IO ()) -> Vector Text -> IO () Source #
Run search create a new session for the searcher to run in, forks a process in which the searchLoop
is run in the background and exits.
runSearchStdIn :: SearchFunctions a -> (Handle -> [Text] -> IO ()) -> IO () Source #
Version of runSearch
in which the vector of candidates is built by reading lines from stdin.
runSearchStdInDef :: SearchFunctions a -> IO () Source #
Version of runSearchStdIn
which uses showMatch
to put the output on the handle.
runSearchStdInColor :: SearchFunctions a -> IO () Source #
Version of runSearchStdIn
for viewing the matches on a terminal which uses showMatchColor
to put the output on the handle.
showMatch :: Handle -> [Text] -> IO () Source #
Outputs the parts of a matching candidate to handle as space separated double quoted strings alternating between a match and a gap. The first text is always a gap and can be empty the rest should be non-empty
Seeker
Default program
run is a small demo program for the piped search. Run `talash piped` to see usage information.
Exposed Internals
:: SearchFunctions a | The functions determining how to much. |
-> Vector Text | The vector of candidates. |
-> Text | The text to match |
-> SearchResult | The last result result. This is used to determine which candidates to search among. |
-> SearchResult |
:: SearchFunctions a | |
-> (Handle -> [Text] -> IO ()) | The functions that determines how a results is presented. Must not introduce newlines. |
-> IOPipes | The handles to the named pipes |
-> Vector Text | The candidates |
-> SearchResult | The last search result |
-> IO (Maybe SearchResult) | The final result. The Nothing is for the case if the input was empty signalling that the searcher should exit. |
One search event consisiting of the searcher reading a bytestring from the input named pipe. If the bytestring is empty the searcher exists. If not it outputs the search results to the output handle and also returns them.
The first line of the output of results is the query. The second is an decimal integer n
which is the number of results to follow. There are n
more lines each
contaning a result presented according the function supplied.
withIOPipes :: (IOPipes -> IO a) -> IO a Source #
Run an IO action that needs two handles to named pipes by creating two named pipes, opening the handles to them performing the action
and then cleaning up by closing the handles and deleting the named pipes created. The names of the pipes are printed on the stdout and are of the
form /tmp/talash-input-pipe
or /tmp/talash-input-pipe<n>
where n is an integer for the input-pipe and /tmp/talash-output-pipe
or
/tmp/talash-output-pipe<n>
for the output pipe. The integer n
will be the same for both.
:: SearchFunctions a | The configuration to use to carry out the search. |
-> Vector Text | The vector |
-> Maybe Text | The query string |
-> Vector Int | The subset of indices of |
-> (Vector Int, (Int, Vector [Text])) | The indices of the matched candidates (see the note above) and the matched candidates broken up according to the match. |
searchWithMatcher carries out one step of the search. Note that the search can stops before going through the whole vector of text. In that case the returned vector of indices should contain not only the indices matched candidates but also the indices of candidates that weren't tested for a match.
readVectorStdIn :: IO (Vector Text) Source #
Read a vector of newline separated candidates from the stdin.
readVectorHandle :: Handle -> IO (Vector Text) Source #
Read a vector of newline separated candidates from a handle.
:: (Text -> Text) | The function to transform the candidates. |
-> (Vector Text -> Vector Text) | The function to apply to the constructed vector before compacting. |
-> Handle | The handle to read from |
-> IO (Vector Text) |
A generalized version of readVectorHandle allowing for the transformation of candidates and the resulting vector. See fileNamesSorted for an example of use.