talash-0.3.0: Line oriented fast enough text search
Safe HaskellSafe-Inferred
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 [ErrorMessage] 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

Documentation

data Searcher a Source #

Constructors

forall n.KnownNat n => Searcher 

Fields

data SearchEvent a Source #

Constructors

forall n.KnownNat n => SearchEvent (SearchEventSized n a) 

data SearchEnv n a b Source #

The constant environment in which the search runs.

Constructors

SearchEnv 

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 AppSettingsG (n :: Nat) a b t Source #

Constructors

AppSettings 

Fields

data CaseSensitivity #

Constructors

CaseSensitive 
IgnoreCase 

Instances

Instances details
FromJSON CaseSensitivity 
Instance details

Defined in Data.Text.CaseSensitivity

ToJSON CaseSensitivity 
Instance details

Defined in Data.Text.CaseSensitivity

Generic CaseSensitivity 
Instance details

Defined in Data.Text.CaseSensitivity

Associated Types

type Rep CaseSensitivity :: Type -> Type #

Show CaseSensitivity 
Instance details

Defined in Data.Text.CaseSensitivity

NFData CaseSensitivity 
Instance details

Defined in Data.Text.CaseSensitivity

Methods

rnf :: CaseSensitivity -> () #

Eq CaseSensitivity 
Instance details

Defined in Data.Text.CaseSensitivity

Hashable CaseSensitivity 
Instance details

Defined in Data.Text.CaseSensitivity

type Rep CaseSensitivity 
Instance details

Defined in Data.Text.CaseSensitivity

type Rep CaseSensitivity = D1 ('MetaData "CaseSensitivity" "Data.Text.CaseSensitivity" "alfred-margaret-2.0.0.0-5xj5mmrDprP1Dn3hNNnaoN" 'False) (C1 ('MetaCons "CaseSensitive" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IgnoreCase" 'PrefixI 'False) (U1 :: Type -> Type))

The Brick App and Helpers

searchApp :: KnownNat n => AppSettings n a -> SearchEnv n a Text -> App (Searcher a) (SearchEvent a) Bool Source #

Tha app itself. selected and the related functions are probably more convenient for embedding into a larger program.

defSettings :: KnownNat n => AppSettings n a Source #

Default settings. Uses blue for various highlights and cyan for borders. All the hooks except keyHook which is handleKeyEvent are trivial.

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

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

selectedIndex :: KnownNat n => AppSettings n a -> SearchFunctions a Text -> 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).

Lenses

Searcher

query :: forall n a b. Lens' (SearchEnv n a b) (MVar (Maybe Text)) Source #

allMatches :: forall n a b. Lens' (SearchEnv n a b) (IOVector (Vector n Bit)) Source #

matches :: forall n a. Lens' (SearcherSized n a) (GenericList Bool MatchSetG (ScoredMatchSized n)) Source #

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

SearchEvent

matchedTop :: forall n a. Lens' (SearchEventSized n a) (MatchSetSized n) Source #

term :: forall n a. Lens' (SearchEventSized n a) Text Source #

SearchEnv

searchFunctions :: forall n a b b. Lens (SearchEnv n a b) (SearchEnv n a b) (SearchFunctions a b) (SearchFunctions a b) Source #

candidates :: forall n a b. Lens' (SearchEnv n a b) (Chunks n) Source #

eventSource :: forall n a. Lens' (SearcherSized n a) (BChan (SearchEvent a)) Source #

AppTheme

SearchSettings

theme :: forall n a b t t. Lens (AppSettingsG n a b t) (AppSettingsG n a b t) t t Source #

hooks :: forall n a b t a b. Lens (AppSettingsG n a b t) (AppSettingsG n a b t) (ReaderT (SearchEnv n a b) EventHooks (Searcher a)) (ReaderT (SearchEnv n a b) EventHooks (Searcher a)) Source #

Exposed Internals

handleKeyEvent :: KnownNat n => SearchEnv n a c -> Key -> [Modifier] -> EventM Bool (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.

searcherWidget :: (KnownNat n, KnownNat m) => AppTheme -> SearchEnv n a Text -> SearcherSized m a -> Widget Bool Source #

The brick widget used to display the editor and the search result.

initialSearcher :: SearchEnv n a c -> BChan (SearchEvent a) -> SearcherSized 0 a Source #

The initial state of the searcher. The editor is empty.

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

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

runApp' :: KnownNat n => AppSettings n a -> SearchFunctions a Text -> Chunks n -> IO (Searcher a) Source #

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

selected' :: KnownNat n => AppSettings n a -> SearchFunctions a Text -> Chunks n -> IO (Maybe [Text]) Source #

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

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

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