talash-0.1.0.0: Line oriented fast enough text search
Safe HaskellNone
LanguageHaskell2010

Talash.Brick.Columns

Description

This module is a quick hack to enable representation of data with columns of text. We use the fact the since the candidates are supposed to fit in a line, they can't have a newlines but text with newlines can otherwise be searched normally. We use this here to separate columns by newlines. Like in Talash.Brick the candidates comes from vector of text. Each such text consists of a fixed number of lines each representing a column. We match against such text and partsColumns then uses the newlines to reconstruct the columns and the parts of the match within each column. This trick of using newline saves us from dealing with the partial state of the match when we cross a column but there is probably a better way . The function runApp , selected and selectedIndex hide this and instead take as argument a Vector [Text] with each element of the list representing a column. Each list must have the same length. Otherwise this module provides a reduced version of the functions in Talash.Brick.

Synopsis

Types

data Searcher a Source #

Constructors

Searcher 

Fields

  • _query :: Editor Text Bool

    The editor to get the query from.

  • _prevQuery :: Maybe Text

    The last query which is saved to check if we should only search among the matches for it or all the candidates.

  • _allMatches :: IORef (Vector Int)

    An IORef containing the indices of the filtered candidates. These are in an IORef to make it easier to deal with them in a different thread than the UI of the app. Maybe it should be moved to SearchEnv

  • _matches :: List Bool [[Text]]

    Each outer list reprsents a column. The inner list is the text for that column split up as an alternating sequences of match substrings and the gap between them. The first substring is always a gap and can be empty, the rest should be no empty.

  • _numMatches :: Int

    The (maximum possible) number of matches. This is the length of vector stored in _allMatches which also contains the indices of which weren't matched in case enough matches were found before going through all the candidates.

  • _wait :: Maybe ThreadId

    ThreadId of the thread currently computing matches. Nothing if there is no such thread.

  • _extension :: a

    Unused by default but can be used store extra state needed for any extension to the functionality. For example to have multiple selections this can be set to a Vector that stores them.

Instances

Instances details
Functor Searcher Source # 
Instance details

Defined in Talash.Brick.Columns

Methods

fmap :: (a -> b) -> Searcher a -> Searcher b #

(<$) :: a -> Searcher b -> Searcher a #

data SearchEvent Source #

Constructors

SearchEvent 

Fields

data SearchEnv a Source #

The constant environment in which they search app runs.

Constructors

SearchEnv 

Fields

data SearchFunctions a Source #

Constructors

SearchFunctions 

Fields

data EventHooks a Source #

Event hooks are almost direct translations of the events from vty i.e. see Event.

Constructors

EventHooks 

Fields

data AppTheme Source #

Constructors

AppTheme 

Fields

data AppSettings a b Source #

Constructors

AppSettings 

Fields

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 minimum number of parts of. 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".

selected :: AppSettings a () -> SearchFunctions a -> Vector [Text] -> IO (Maybe [Text]) Source #

Run app and return the the selection if there is one else Nothing.

selectedIndex :: AppSettings a () -> SearchFunctions a -> Vector [Text] -> IO (Maybe Int) Source #

Returns the index of selected candidate in the vector of candidates. Note: it uses elemIndex which is O(N).

runApp :: b -> AppSettings a b -> SearchFunctions a -> Vector [Text] -> IO (Searcher b) Source #

Run app with given settings and return the final Searcher state.

Lenses

Searcher

query :: forall a. Lens' (Searcher a) (Editor Text Bool) Source #

matches :: forall a. Lens' (Searcher a) (List Bool [[Text]]) Source #

numMatches :: forall a. Lens' (Searcher a) Int Source #

wait :: forall a. Lens' (Searcher a) (Maybe ThreadId) Source #

SearchEvent

SearchEnv

SearchFunctions

displayer :: forall a n. KnownNat n => SimpleGetter (SearchFunctions a) (MatcherSized n a -> Text -> Vector n Int -> [[Text]]) Source #

AppTheme

SearchSettings

theme :: forall a b. Lens' (AppSettings a b) AppTheme Source #

Exposed Internals

makeQuery :: Searcher a -> Maybe Text Source #

Get the current query from the editor of the searcher.

haltQuit :: Searcher a -> EventM n (Next (Searcher a)) Source #

Quit without any selection.

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.

replaceSearch :: Bool -> SearchEnv a -> Searcher b -> IO ThreadId Source #

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 :: 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 :: [AttrName] -> [Int] -> 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.

searchWithMatcher :: SearchFunctions a -> Vector Text -> Maybe Text -> Vector Int -> (Vector Int, (Int, Vector [[Text]])) Source #

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.

partsColumns :: [Text] -> [[Text]] Source #

This function reconstructs the columns from the parts returned by the search by finding the newlines.

runApp' :: b -> AppSettings a b -> SearchFunctions a -> Vector Text -> IO (Searcher b) Source #

The 'raw' version of runApp taking a vector of text with columns separated by newlines.

selected' :: AppSettings a () -> SearchFunctions a -> Vector Text -> IO (Maybe [Text]) Source #

The 'raw' version of selected taking a vector of text with columns separated by newlines.

selectedIndex' :: AppSettings a () -> SearchFunctions a -> Vector Text -> IO (Maybe Int) Source #

The 'raw' version of selectedIndex taking a vector of text with columns separated by newlines.