Safe Haskell | Safe-Inferred |
---|---|
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 PipedSearcher = PipedSearcher {
- _inputHandle :: Handle
- _outputHandle :: Handle
- _maximumMatches :: Int
- _printStrategy :: SearchReport -> Bool
- _printer :: Handle -> [Text] -> IO ()
- query :: forall n a b. Lens' (SearchEnv n a b) (MVar (Maybe Text))
- allMatches :: forall n a b. Lens' (SearchEnv n a b) (IOVector (Vector n Bit))
- data CaseSensitivity
- searchLoop :: KnownNat n => SearchEnv n a b -> IO ()
- runSearch :: KnownNat n => IO () -> SearchFunctions a Text -> PipedSearcher -> Chunks n -> IO ()
- runSearchStdIn :: KnownNat n => Proxy n -> IO () -> SearchFunctions a Text -> PipedSearcher -> IO ()
- runSearchStdInDef :: SearchFunctions a Text -> IO ()
- showMatchColor :: Handle -> [Text] -> IO ()
- askSearcher :: String -> String -> Text -> IO ()
- run :: IO ()
- run' :: [String] -> IO ()
- withNamedPipes :: (IO () -> Handle -> Handle -> IO a) -> IO a
- send :: String -> Text -> IO ()
- recieve :: String -> IO ()
Types and Lenses
data PipedSearcher Source #
PipedSearcher | |
|
data CaseSensitivity #
Instances
runSearch :: KnownNat n => IO () -> SearchFunctions a Text -> PipedSearcher -> Chunks n -> 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 :: KnownNat n => Proxy n -> IO () -> SearchFunctions a Text -> PipedSearcher -> IO () Source #
Version of runSearch
in which the vector of candidates is built by reading lines from stdin.
runSearchStdInDef :: SearchFunctions a Text -> IO () Source #
Version of runSearchStdIn
which uses showMatch
to put the output on the handle.
showMatchColor :: Handle -> [Text] -> IO () Source #
Outputs a matching candidate for the terminal with the matches highlighted in blue. Uses the Colored
ErrorMessage
monoid from `colorful-monoids` for coloring.
run is a small demo program for the piped search. Run `talash piped` to see usage information.
withNamedPipes :: (IO () -> Handle -> Handle -> 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.