Safe Haskell | None |
---|---|
Language | Haskell2010 |
A simple brick app to search among the candidates from a vector of text and get the selection. By default the app doesn't do anything except
return a single selection but more complicated actions can be performed by using the _hooks
which allow abitrary IO actions (due to EventM
being a MonadIO
)
in response to input events. The most convenient function to use the brick app are selected
and related functions. runApp
provides some more flexibility.
Synopsis
- data Searcher a = Searcher {}
- data SearchEvent = SearchEvent {
- _matchedTop :: Vector [Text]
- _totalMatches :: Int
- _term :: Maybe Text
- data SearchEnv a = SearchEnv {}
- data SearchFunctions a = SearchFunctions {}
- data EventHooks a = EventHooks {
- keyHook :: Key -> [Modifier] -> a -> EventM Bool (Next a)
- pasteHook :: ByteString -> a -> EventM Bool (Next a)
- resizeHook :: Int -> Int -> a -> EventM Bool (Next a)
- mouseDownHook :: Int -> Int -> Button -> [Modifier] -> a -> EventM Bool (Next a)
- mouseUpHook :: Int -> Int -> Maybe Button -> a -> EventM Bool (Next a)
- focusLostHook :: a -> EventM Bool (Next a)
- focusGainedHook :: a -> EventM Bool (Next a)
- data AppTheme = AppTheme {
- _prompt :: Text
- _themeAttrs :: [(AttrName, Attr)]
- _borderStyle :: BorderStyle
- data AppSettings a b = AppSettings {}
- searchApp :: AppSettings a b -> SearchEnv a -> App (Searcher b) SearchEvent Bool
- defSettings :: AppSettings a b
- searchFunctionsFuzzy :: SearchFunctions MatchPart
- searchFunctionsOL :: SearchFunctions Int
- runApp :: b -> AppSettings a b -> SearchFunctions a -> Vector Text -> IO (Searcher b)
- runAppFromHandle :: b -> AppSettings a b -> SearchFunctions a -> Handle -> IO (Searcher b)
- selected :: AppSettings a () -> SearchFunctions a -> Vector Text -> IO (Maybe Text)
- selectedFromHandle :: AppSettings a () -> SearchFunctions a -> Handle -> IO (Maybe Text)
- selectedFromHandleWith :: (Text -> Text) -> (Vector Text -> Vector Text) -> AppSettings a () -> SearchFunctions a -> Handle -> IO (Maybe Text)
- selectedFromFileNamesSorted :: AppSettings a () -> SearchFunctions a -> Handle -> IO (Maybe Text)
- selectedFromFiles :: AppSettings a () -> SearchFunctions a -> [FindInDirs] -> IO (Maybe Text)
- runSearch :: AppSettings a () -> SearchFunctions a -> IO ()
- run :: IO ()
- run' :: [String] -> IO ()
- query :: forall a. Lens' (Searcher a) (Editor Text Bool)
- prevQuery :: forall a. Lens' (Searcher a) (Maybe Text)
- allMatches :: forall a. Lens' (Searcher a) (IORef (Vector Int))
- matches :: forall a. Lens' (Searcher a) (List Bool [Text])
- numMatches :: forall a. Lens' (Searcher a) Int
- wait :: forall a. Lens' (Searcher a) (Maybe ThreadId)
- matchedTop :: Lens' SearchEvent (Vector [Text])
- totalMatches :: Lens' SearchEvent Int
- term :: Lens' SearchEvent (Maybe Text)
- searchFunctions :: forall a a. Lens (SearchEnv a) (SearchEnv a) (SearchFunctions a) (SearchFunctions a)
- candidates :: forall a. Lens' (SearchEnv a) (Vector Text)
- eventSource :: forall a. Lens' (SearchEnv a) (BChan SearchEvent)
- 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])
- prompt :: Lens' AppTheme Text
- themeAttrs :: Lens' AppTheme [(AttrName, Attr)]
- borderStyle :: Lens' AppTheme BorderStyle
- theme :: forall a b. Lens' (AppSettings a b) AppTheme
- hooks :: forall a b a b. Lens (AppSettings a b) (AppSettings a b) (ReaderT (SearchEnv a) EventHooks (Searcher b)) (ReaderT (SearchEnv a) EventHooks (Searcher b))
- makeQuery :: Searcher a -> Maybe Text
- haltQuit :: Searcher a -> EventM n (Next (Searcher a))
- handleKeyEvent :: SearchEnv a -> Key -> [Modifier] -> Searcher b -> EventM Bool (Next (Searcher b))
- handleSearch :: Vector Text -> Searcher a -> SearchEvent -> EventM Bool (Next (Searcher a))
- editStep :: SearchEnv a -> Searcher b -> IO (Searcher b)
- replaceSearch :: Bool -> SearchEnv a -> Searcher b -> IO ThreadId
- search :: forall a. SearchFunctions a -> Vector Text -> Maybe Text -> IORef (Vector Int) -> IO SearchEvent
- searcherWidget :: Text -> Text -> Searcher a -> Widget Bool
- initialSearcher :: a -> Vector Text -> IORef (Vector Int) -> Searcher a
- 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
Searcher | |
|
data SearchEvent Source #
SearchEvent | |
|
The constant environment in which the search app runs.
SearchEnv | |
|
data SearchFunctions a Source #
SearchFunctions | |
|
data EventHooks a Source #
Event hooks are almost direct translations of the events from vty i.e. see Event
.
EventHooks | |
|
AppTheme | |
|
data AppSettings a b Source #
The Brick App and Helpers
searchApp :: AppSettings a b -> SearchEnv a -> App (Searcher b) SearchEvent Bool Source #
Tha app itself. selected
and the related functions are probably more convenient for embedding into a larger program.
defSettings :: AppSettings a b Source #
Default settings. Uses blue for various highlights and cyan for borders. All the hooks except keyHook which is handleKeyEvent
are trivial.
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.
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"
.
runApp :: b -> AppSettings a b -> SearchFunctions a -> Vector Text -> IO (Searcher b) Source #
Run app with given settings and return the final Searcher state.
runAppFromHandle :: b -> AppSettings a b -> SearchFunctions a -> Handle -> IO (Searcher b) Source #
Run app with a vector that contains lines read from a handle and return the final Searcher state.
selected :: AppSettings a () -> SearchFunctions a -> Vector Text -> IO (Maybe Text) Source #
Run app and return the text of the selection if there is one else Nothing.
selectedFromHandle :: AppSettings a () -> SearchFunctions a -> Handle -> IO (Maybe Text) Source #
Same as selected
but reads the vector from the supplied handle.
selectedFromHandleWith :: (Text -> Text) -> (Vector Text -> Vector Text) -> AppSettings a () -> SearchFunctions a -> Handle -> IO (Maybe Text) Source #
Same as selectedFromHandle
but allows for transforming the lines read and the final vector with supplied functions. See also readVectorHandleWith
.
selectedFromFileNamesSorted :: AppSettings a () -> SearchFunctions a -> Handle -> IO (Maybe Text) Source #
Another variation on selectedFromHandle
. See fileNamesSorted
for what happens to read vector.
selectedFromFiles :: AppSettings a () -> SearchFunctions a -> [FindInDirs] -> IO (Maybe Text) Source #
Version of selected
for file search using a simple implementation of searching file trees from Talash.Files. Better to use either other
libraries like unix-recursive
or external programs like fd
for more complicated tasks.
runSearch :: AppSettings a () -> SearchFunctions a -> IO () Source #
A version of selected
that puts the selected text on the stdout.
Default program
Defualt program for the brick app that reads candidates from stdin and prints the selected text to the stdout. Can be called from the executable with
talash tui
which uses the orderless style. The search style can be set explicitly by calling talash tui fuzzy
or talash tui orderless
Lenses
Searcher
SearchEvent
matchedTop :: Lens' SearchEvent (Vector [Text]) Source #
SearchEnv
searchFunctions :: forall a a. Lens (SearchEnv a) (SearchEnv a) (SearchFunctions a) (SearchFunctions a) Source #
eventSource :: forall a. Lens' (SearchEnv a) (BChan SearchEvent) 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 #
AppTheme
SearchSettings
hooks :: forall a b a b. Lens (AppSettings a b) (AppSettings a b) (ReaderT (SearchEnv a) EventHooks (Searcher b)) (ReaderT (SearchEnv a) EventHooks (Searcher b)) Source #
Exposed Internals
makeQuery :: Searcher a -> Maybe Text Source #
Get the current query from the editor of the searcher.
handleKeyEvent :: SearchEnv a -> Key -> [Modifier] -> Searcher b -> EventM Bool (Next (Searcher b)) Source #
Handling of keypresses. The default bindings are
Enter
exits the app with the current selection.
Esc
exits without any selection
Up
, Down
, PageUp
and PageDown
move through the matches.
All others keys are used for editing the query. See handleEditorEvent
for details.
handleSearch :: Vector Text -> Searcher a -> SearchEvent -> EventM Bool (Next (Searcher a)) Source #
Handle a search event by updating _numMatches
, _matches
and _wait
.
editStep :: SearchEnv a -> Searcher b -> IO (Searcher b) Source #
Handle the editing of the query by starting the computation of the matches in a new thread and storing the ThreadId
in _wait
.
If the new query contains the last query then doesn't try to match the candidates that didn't match the last query, otherwise search among all the candidates.
Might be possible to make the performance better by storing the indices of the filtered candidates for more than one previous query.
:: Bool | If True then search among all matches by writing a vector of all the indices into |
-> SearchEnv a | |
-> Searcher b | |
-> IO ThreadId |
This function dispatches the computation of matches to a new thread and returns the new threadId. It also tries to kill the thread in which a previous computation was going on (Not sure if it actually accomplishes that, my understanding of exceptions is not good enough).
search :: forall a. SearchFunctions a -> Vector Text -> Maybe Text -> IORef (Vector Int) -> IO SearchEvent Source #
The functions for generating a search event. It is executed in a separate thread via forkIO
in replaceSearch
.
searcherWidget :: Text -> Text -> Searcher a -> Widget Bool Source #
The brick widget used to display the editor and the search result.
initialSearcher :: a -> Vector Text -> IORef (Vector Int) -> Searcher a Source #
The initial state of the searcher. The editor is empty, the first 512
elements of the vector are disaplyed as matches.
:: 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.